Skip to content

Commit

Permalink
tools: implement OSV conversion
Browse files Browse the repository at this point in the history
Add the `Security.Advisories.Convert.OSV` module, which defines the
conversion from our `Advisory` data type to the OSV `Model`.
Currently, no database-specific or ecosystem-specific fields are
set.  Whether or how to use those fields is a matter for future
discussion.

Add the `osv` subcommand to `hsec-tools`.  It works in the same way
as `check`, but emits the encoded OSV JSON data.

Later commits will add the CI workflows to generate and publish the
OSV data.

Fixes: #3
  • Loading branch information
frasertweedale committed Jun 28, 2023
1 parent 1c0fd46 commit 8ee2421
Show file tree
Hide file tree
Showing 3 changed files with 78 additions and 0 deletions.
15 changes: 15 additions & 0 deletions code/hsec-tools/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
module Main where

import Control.Monad (join, void, when)
import qualified Data.ByteString.Lazy as L
import Data.Foldable (for_)
import Data.Functor ((<&>))
import Data.List (isPrefixOf)
Expand All @@ -14,7 +15,10 @@ import System.Exit (die, exitFailure, exitSuccess)
import System.IO (stderr)
import System.FilePath (takeBaseName)

import qualified Data.Aeson

import Security.Advisories
import qualified Security.Advisories.Convert.OSV as OSV
import Security.Advisories.Git

main :: IO ()
Expand All @@ -27,6 +31,7 @@ cliOpts = info (commandsParser <**> helper) (fullDesc <> header "Haskell Advisor
commandsParser =
subparser
( command "check" (info commandCheck mempty)
<> command "osv" (info commandOsv mempty)
<> command "render" (info commandRender mempty)
<> command "help" (info commandHelp mempty)
)
Expand All @@ -44,6 +49,16 @@ commandCheck =
die $ "Filename does not match advisory ID: " <> path
T.putStrLn "no error"

commandOsv :: Parser (IO ())
commandOsv =
withAdvisory go
<$> optional (argument str (metavar "FILE"))
<**> helper
where
go _ adv = do
L.putStr (Data.Aeson.encode (OSV.convert adv))
putChar '\n'

commandRender :: Parser (IO ())
commandRender =
withAdvisory (\_ -> T.putStrLn . advisoryHtml)
Expand Down
3 changes: 3 additions & 0 deletions code/hsec-tools/hsec-tools.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@ library
, Security.Advisories.Definition
, Security.Advisories.Git
, Security.Advisories.Parse
, Security.Advisories.Convert.OSV
, Security.OSV
build-depends: base >=4.14 && < 4.19,
filepath >= 1.4 && < 1.5,
Expand Down Expand Up @@ -66,6 +67,8 @@ executable hsec-tools
-- other-extensions:
build-depends: hsec-tools,
base >=4.14 && < 4.19,
aeson >= 2,
bytestring >= 0.10 && < 0.12,
text >= 1.2 && < 3,
optparse-applicative == 0.17.* || == 0.18.*,
filepath >= 1.4 && < 1.5
Expand Down
60 changes: 60 additions & 0 deletions code/hsec-tools/src/Security/Advisories/Convert/OSV.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,60 @@
{-# LANGUAGE OverloadedStrings #-}

module Security.Advisories.Convert.OSV
( convert
)
where

import qualified Data.Text as T
import Data.Time (zonedTimeToUTC)
import Data.Void

import Security.Advisories
import qualified Security.OSV as OSV

convert :: Advisory -> OSV.Model Void Void Void Void
convert adv =
( OSV.newModel'
(advisoryId adv)
(zonedTimeToUTC $ advisoryModified adv)
)
{ OSV.modelPublished = Just $ zonedTimeToUTC (advisoryPublished adv)
, OSV.modelAliases = advisoryAliases adv
, OSV.modelSummary = Just $ advisorySummary adv
, OSV.modelDetails = Just $ advisoryDetails adv
, OSV.modelReferences = advisoryReferences adv
, OSV.modelAffected = fmap mkAffected (advisoryAffected adv)
}

mkAffected :: Affected -> OSV.Affected Void Void Void
mkAffected aff =
OSV.Affected
{ OSV.affectedPackage = mkPackage (affectedPackage aff)
, OSV.affectedRanges = pure $ mkRange (affectedVersions aff)
, OSV.affectedSeverity = mkSeverity (affectedCVSS aff)
, OSV.affectedEcosystemSpecific = Nothing
, OSV.affectedDatabaseSpecific = Nothing
}

mkPackage :: T.Text -> OSV.Package
mkPackage name = OSV.Package
{ OSV.packageName = name
, OSV.packageEcosystem = "Hackage"
, OSV.packagePurl = Nothing
}

-- NOTE: This is unpleasant. But we will eventually switch to a
-- proper CVSS type and the unpleasantness will go away.
--
mkSeverity :: T.Text -> [OSV.Severity]
mkSeverity s = case T.take 6 s of
"CVSS:2" -> [OSV.SeverityCvss2 s]
"CVSS:3" -> [OSV.SeverityCvss3 s]
_ -> [] -- unexpected; don't include severity

mkRange :: [AffectedVersionRange] -> OSV.Range Void
mkRange ranges = OSV.RangeEcosystem (foldMap mkEvs ranges) Nothing
where
mkEvs range =
OSV.EventIntroduced (affectedVersionRangeIntroduced range)
: maybe [] (pure . OSV.EventFixed) (affectedVersionRangeFixed range)

0 comments on commit 8ee2421

Please sign in to comment.