Skip to content

Commit

Permalink
Rename Ecosystem into ComponentIdentifier
Browse files Browse the repository at this point in the history
  • Loading branch information
TristanCacqueray committed Jul 20, 2024
1 parent 85c27ad commit 126e17b
Show file tree
Hide file tree
Showing 12 changed files with 36 additions and 36 deletions.
6 changes: 3 additions & 3 deletions code/hsec-core/src/Security/Advisories/Core/Advisory.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ module Security.Advisories.Core.Advisory
, AffectedVersionRange(..)
, OS(..)
, Keyword(..)
, Ecosystem(..)
, ComponentIdentifier(..)
, GHCComponent(..)
, ghcComponentToText
, ghcComponentFromText
Expand Down Expand Up @@ -48,7 +48,7 @@ data Advisory = Advisory
}
deriving stock (Show)

data Ecosystem = Hackage Text | GHC GHCComponent
data ComponentIdentifier = Hackage Text | GHC GHCComponent
deriving stock (Show, Eq)

-- Keep this list in sync with the 'ghcComponentFromText' below
Expand All @@ -71,7 +71,7 @@ ghcComponentFromText c = case c of
-- | An affected package (or package component). An 'Advisory' must
-- mention one or more packages.
data Affected = Affected
{ affectedEcosystem :: Ecosystem
{ affectedComponentIdentifier :: ComponentIdentifier
, affectedCVSS :: CVSS.CVSS
, affectedVersions :: [AffectedVersionRange]
, affectedArchitectures :: Maybe [Architecture]
Expand Down
6 changes: 3 additions & 3 deletions code/hsec-tools/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ import Security.Advisories.Generate.HTML
import Security.Advisories.Generate.Snapshot
import Security.Advisories.Git
import Security.Advisories.Queries (listVersionRangeAffectedBy)
import Security.Advisories.Filesystem (parseEcosystem)
import Security.Advisories.Filesystem (parseComponentIdentifier)
import System.Exit (die, exitFailure, exitSuccess)
import System.FilePath (takeBaseName)
import System.IO (hPrint, hPutStrLn, stderr)
Expand Down Expand Up @@ -169,13 +169,13 @@ withAdvisory go file = do
oob <- runExceptT $ case file of
Nothing -> throwE StdInHasNoOOB
Just path -> do
ecosystem <- parseEcosystem path
ecosystem <- parseComponentIdentifier path
withExceptT GitHasNoOOB $ do
gitInfo <- ExceptT $ liftIO $ getAdvisoryGitInfo path
pure OutOfBandAttributes
{ oobPublished = firstAppearanceCommitDate gitInfo
, oobModified = lastModificationCommitDate gitInfo
, oobEcosystem = ecosystem
, oobComponentIdentifier = ecosystem
}

case parseAdvisory NoOverrides oob input of
Expand Down
4 changes: 2 additions & 2 deletions code/hsec-tools/src/Security/Advisories/Convert/OSV.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,14 +30,14 @@ convert adv =
mkAffected :: Affected -> OSV.Affected Void Void Void
mkAffected aff =
OSV.Affected
{ OSV.affectedPackage = mkPackage (affectedEcosystem aff)
{ OSV.affectedPackage = mkPackage (affectedComponentIdentifier aff)
, OSV.affectedRanges = pure $ mkRange (affectedVersions aff)
, OSV.affectedSeverity = [OSV.Severity (affectedCVSS aff)]
, OSV.affectedEcosystemSpecific = Nothing
, OSV.affectedDatabaseSpecific = Nothing
}

mkPackage :: Ecosystem -> OSV.Package
mkPackage :: ComponentIdentifier -> OSV.Package
mkPackage ecosystem = OSV.Package
{ OSV.packageName = packageName
, OSV.packageEcosystem = ecosystemName
Expand Down
16 changes: 8 additions & 8 deletions code/hsec-tools/src/Security/Advisories/Filesystem.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ module Security.Advisories.Filesystem
, forAdvisory
, listAdvisories
, advisoryFromFile
, parseEcosystem
, parseComponentIdentifier
) where

import Control.Applicative (liftA2)
Expand All @@ -39,11 +39,11 @@ import System.Directory (doesDirectoryExist, pathIsSymbolicLink)
import System.Directory.PathWalk
import Validation (Validation (..))

import Security.Advisories (Advisory, AttributeOverridePolicy (NoOverrides), OutOfBandAttributes (..), ParseAdvisoryError, parseAdvisory, Ecosystem(..))
import Security.Advisories (Advisory, AttributeOverridePolicy (NoOverrides), OutOfBandAttributes (..), ParseAdvisoryError, parseAdvisory, ComponentIdentifier(..))
import Security.Advisories.Core.HsecId (HsecId, parseHsecId, placeholder)
import Security.Advisories.Git(firstAppearanceCommitDate, getAdvisoryGitInfo, lastModificationCommitDate)
import Control.Monad.Except (runExceptT, ExceptT (ExceptT), withExceptT)
import Security.Advisories.Parse (OOBError(GitHasNoOOB, PathHasNoEcosystem))
import Security.Advisories.Parse (OOBError(GitHasNoOOB, PathHasNoComponentIdentifier))
import Security.Advisories.Core.Advisory (ghcComponentFromText)


Expand Down Expand Up @@ -138,13 +138,13 @@ advisoryFromFile
=> FilePath -> m (Validation ParseAdvisoryError Advisory)
advisoryFromFile advisoryPath = do
oob <- runExceptT $ do
ecosystem <- parseEcosystem advisoryPath
ecosystem <- parseComponentIdentifier advisoryPath
withExceptT GitHasNoOOB $ do
gitInfo <- ExceptT $ liftIO $ getAdvisoryGitInfo advisoryPath
pure OutOfBandAttributes
{ oobPublished = firstAppearanceCommitDate gitInfo
, oobModified = lastModificationCommitDate gitInfo
, oobEcosystem = ecosystem
, oobComponentIdentifier = ecosystem
}
fileContent <- liftIO $ T.readFile advisoryPath
pure
Expand Down Expand Up @@ -174,9 +174,9 @@ _forFiles root go =
Nothing -> pure mempty
Just hsid -> go (dir </> file) hsid

parseEcosystem :: Monad m => FilePath -> ExceptT OOBError m (Maybe Ecosystem)
parseEcosystem fp = ExceptT . pure $ case drop 1 $ reverse $ splitDirectories fp of
parseComponentIdentifier :: Monad m => FilePath -> ExceptT OOBError m (Maybe ComponentIdentifier)
parseComponentIdentifier fp = ExceptT . pure $ case drop 1 $ reverse $ splitDirectories fp of
package : "hackage" : _ -> pure (Just $ Hackage $ T.pack package)
component : "ghc" : _ | Just ghc <- ghcComponentFromText (T.pack component) -> pure (Just $ GHC ghc)
_ : _ : "advisories" : _ -> Left PathHasNoEcosystem
_ : _ : "advisories" : _ -> Left PathHasNoComponentIdentifier
_ -> pure Nothing
4 changes: 2 additions & 2 deletions code/hsec-tools/src/Security/Advisories/Format.hs
Original file line number Diff line number Diff line change
Expand Up @@ -154,7 +154,7 @@ instance Toml.FromValue Affected where
decls <- maybe [] Map.toList <$> Toml.optKey "declarations"
versions <- Toml.reqKey "versions"
pure $ Affected
{ affectedEcosystem = ecosystem
{ affectedComponentIdentifier = ecosystem
, affectedCVSS = cvss
, affectedVersions = versions
, affectedArchitectures = arch
Expand All @@ -175,7 +175,7 @@ instance Toml.ToTable Affected where
[ "arch" Toml..= y | Just y <- [affectedArchitectures x]] ++
[ "declarations" Toml..= asTable (affectedDeclarations x) | not (null (affectedDeclarations x))]
where
ecosystem = case affectedEcosystem x of
ecosystem = case affectedComponentIdentifier x of
Hackage pkg -> ["package" Toml..= pkg]
GHC c -> ["ghc-component" Toml..= c]
asTable kvs = Map.fromList [(T.unpack k, v) | (k,v) <- kvs]
Expand Down
6 changes: 3 additions & 3 deletions code/hsec-tools/src/Security/Advisories/Generate/HTML.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ import Validation (Validation (..))
import qualified Security.Advisories as Advisories
import Security.Advisories.Filesystem (listAdvisories)
import Security.Advisories.Generate.TH (readDirFilesTH)
import Security.Advisories.Core.Advisory (Ecosystem (..), ghcComponentToText)
import Security.Advisories.Core.Advisory (ComponentIdentifier (..), ghcComponentToText)

-- * Actions

Expand Down Expand Up @@ -88,7 +88,7 @@ data AdvisoryR = AdvisoryR
deriving stock (Show)

data AffectedPackageR = AffectedPackageR
{ ecosystem :: Ecosystem,
{ ecosystem :: ComponentIdentifier,
introduced :: Text,
fixed :: Maybe Text
}
Expand Down Expand Up @@ -234,7 +234,7 @@ toAdvisoryR x =
toAffectedPackageR p =
flip map (Advisories.affectedVersions p) $ \versionRange ->
AffectedPackageR
{ ecosystem = Advisories.affectedEcosystem p,
{ ecosystem = Advisories.affectedComponentIdentifier p,
introduced = T.pack $ prettyShow $ Advisories.affectedVersionRangeIntroduced versionRange,
fixed = T.pack . prettyShow <$> Advisories.affectedVersionRangeFixed versionRange
}
Expand Down
16 changes: 8 additions & 8 deletions code/hsec-tools/src/Security/Advisories/Parse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@
, displayOOBError
, AttributeOverridePolicy(..)
, ParseAdvisoryError(..)
, validateEcosystem
, validateComponentIdentifier
)
where

Expand Down Expand Up @@ -64,7 +64,7 @@ type OOB = Either OOBError OutOfBandAttributes
data OutOfBandAttributes = OutOfBandAttributes
{ oobModified :: UTCTime
, oobPublished :: UTCTime
, oobEcosystem :: Maybe Ecosystem
, oobComponentIdentifier :: Maybe ComponentIdentifier
}
deriving (Show)

Expand Down Expand Up @@ -94,14 +94,14 @@ instance Exception ParseAdvisoryError where
-- @since 0.2.0.0
data OOBError
= StdInHasNoOOB -- ^ we obtain the advisory via stdin and can hence not parse git history
| PathHasNoEcosystem -- ^ the path is missing 'hackage' or 'ghc' directory
| PathHasNoComponentIdentifier -- ^ the path is missing 'hackage' or 'ghc' directory
| GitHasNoOOB GitError -- ^ processing oob info via git failed
deriving stock (Eq, Show, Generic)

displayOOBError :: OOBError -> String
displayOOBError = \case
StdInHasNoOOB -> "stdin doesn't provide out of band information"
PathHasNoEcosystem -> "the path is missing 'hackage' or 'ghc' directory"
PathHasNoComponentIdentifier -> "the path is missing 'hackage' or 'ghc' directory"
GitHasNoOOB gitErr -> "no out of band information obtained with git error:\n"
<> explainGitError gitErr

Expand Down Expand Up @@ -191,7 +191,7 @@ parseAdvisoryTable oob policy doc summary details html tab =
(amdModified (frontMatterAdvisory fm))
let affected = frontMatterAffected fm
case oob of
Right (OutOfBandAttributes _ _ (Just ecosystem)) -> validateEcosystem ecosystem affected
Right (OutOfBandAttributes _ _ (Just ecosystem)) -> validateComponentIdentifier ecosystem affected
_ -> pure ()
pure Advisory
{ advisoryId = amdId (frontMatterAdvisory fm)
Expand All @@ -211,9 +211,9 @@ parseAdvisoryTable oob policy doc summary details html tab =
}

-- | Make sure one of the affected match the ecosystem
validateEcosystem :: MonadFail m => Ecosystem -> [Affected] -> m ()
validateEcosystem ecosystem xs
| any (\affected -> affectedEcosystem affected == ecosystem) xs = pure ()
validateComponentIdentifier :: MonadFail m => ComponentIdentifier -> [Affected] -> m ()
validateComponentIdentifier ecosystem xs
| any (\affected -> affectedComponentIdentifier affected == ecosystem) xs = pure ()
| otherwise = fail $ "Expected an affected to match the ecosystem: " <> show ecosystem

advisoryDoc :: Blocks -> Either Text (Text, [Block])
Expand Down
2 changes: 1 addition & 1 deletion code/hsec-tools/src/Security/Advisories/Queries.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ isAffectedByHelper checkWithRange queryPackageName queryVersionish =
any checkAffected . advisoryAffected
where
checkAffected :: Affected -> Bool
checkAffected affected = case affectedEcosystem affected of
checkAffected affected = case affectedComponentIdentifier affected of
Hackage pkg -> queryPackageName == pkg && checkWithRange queryVersionish (fromAffected affected)
-- TODO: support GHC ecosystem query, e.g. by adding a cli flag
_ -> False
Expand Down
2 changes: 1 addition & 1 deletion code/hsec-tools/test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ doGoldenTest fp = goldenVsString fp (fp <> ".golden") (LText.encodeUtf8 <$> doCh
attr = OutOfBandAttributes
{ oobPublished = fakeDate
, oobModified = fakeDate
, oobEcosystem = Nothing
, oobComponentIdentifier = Nothing
}
res = parseAdvisory NoOverrides (Right attr) input
osvExport = case res of
Expand Down
6 changes: 3 additions & 3 deletions code/hsec-tools/test/Spec/FormatSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -70,15 +70,15 @@ genAdvisoryMetadata =
genAffected :: Gen.Gen Affected
genAffected =
Affected
<$> genEcosystem
<$> genComponentIdentifier
<*> genCVSS
<*> Gen.list (Range.linear 0 5) genAffectedVersionRange
<*> Gen.maybe (Gen.list (Range.linear 0 5) genArchitecture)
<*> Gen.maybe (Gen.list (Range.linear 0 5) genOS)
<*> (Map.toList . Map.fromList <$> Gen.list (Range.linear 0 5) ((,) <$> genText <*> genVersionRange))

genEcosystem :: Gen.Gen Ecosystem
genEcosystem = Gen.choice $
genComponentIdentifier :: Gen.Gen ComponentIdentifier
genComponentIdentifier = Gen.choice $
[ Hackage <$> genText
, GHC <$> genGHCComponent
]
Expand Down
2 changes: 1 addition & 1 deletion code/hsec-tools/test/Spec/QueriesSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -115,7 +115,7 @@ mkAdvisory versionRange =
, advisoryRelated = [ "CVE-2022-YYYY" , "CVE-2022-ZZZZ" ]
, advisoryAffected =
[ Affected
{ affectedEcosystem = Hackage packageName
{ affectedComponentIdentifier = Hackage packageName
, affectedCVSS = cvss
, affectedVersions = mkAffectedVersions versionRange
, affectedArchitectures = Nothing
Expand Down
2 changes: 1 addition & 1 deletion code/hsec-tools/test/golden/EXAMPLE_ADVISORY.md.golden
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ Right
]
, advisoryAffected =
[ Affected
{ affectedEcosystem = Hackage "package-name"
{ affectedComponentIdentifier = Hackage "package-name"
, affectedCVSS = CVSS:3.1/AV:N/AC:L/PR:N/UI:N/S:U/C:H/I:H/A:H
, affectedVersions =
[ AffectedVersionRange
Expand Down

0 comments on commit 126e17b

Please sign in to comment.