Skip to content

Commit 80b12de

Browse files
Update hsec-tool to use the new CWE data and validation
1 parent 449337c commit 80b12de

File tree

4 files changed

+32
-12
lines changed

4 files changed

+32
-12
lines changed

code/cwe/src/Security/CWE.hs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
{-# LANGUAGE DerivingStrategies #-}
33
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
44
{-# LANGUAGE OverloadedStrings #-}
5-
module Security.CWE (CWEID, mkCWEID, cweNames, cweIds) where
5+
module Security.CWE (CWEID, unCWEID, mkCWEID, cweNames, cweIds) where
66

77
import Security.CWE.Data
88
import Data.Text (Text)
@@ -14,6 +14,10 @@ import Data.Bits
1414
newtype CWEID = CWEID Word
1515
deriving newtype (Eq, Ord, Show)
1616

17+
-- | Access the underlying data.
18+
unCWEID :: CWEID -> Word
19+
unCWEID (CWEID cwe) = cwe
20+
1721
mkCWEID :: (Integral a, Bits a) => a -> Maybe CWEID
1822
mkCWEID num = CWEID <$> toIntegralSized num
1923

code/hsec-tools/hsec-tools.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,7 @@ library
4949
, commonmark ^>=0.2.2
5050
, commonmark-pandoc >=0.2 && <0.3
5151
, containers >=0.6 && <0.7
52+
, cwe >=0.1 && <2
5253
, directory <2
5354
, extra ^>=1.7.5
5455
, filepath >=1.4 && <1.5

code/hsec-tools/src/Security/Advisories/Definition.hs

Lines changed: 3 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -4,14 +4,15 @@ module Security.Advisories.Definition
44
( Advisory(..)
55
-- * Supporting types
66
, Affected(..)
7-
, CWE(..)
7+
, CWEID
88
, Architecture(..)
99
, AffectedVersionRange(..)
1010
, OS(..)
1111
, Keyword(..)
1212
)
1313
where
1414

15+
import Security.CWE (CWEID)
1516
import Data.Text (Text)
1617
import Data.Time (ZonedTime)
1718
import Distribution.Types.Version (Version)
@@ -26,7 +27,7 @@ data Advisory = Advisory
2627
{ advisoryId :: HsecId
2728
, advisoryModified :: ZonedTime
2829
, advisoryPublished :: ZonedTime
29-
, advisoryCWEs :: [CWE]
30+
, advisoryCWEs :: [CWEID]
3031
, advisoryKeywords :: [Keyword]
3132
, advisoryAliases :: [Text]
3233
, advisoryRelated :: [Text]
@@ -53,9 +54,6 @@ data Affected = Affected
5354
}
5455
deriving stock (Show)
5556

56-
newtype CWE = CWE {unCWE :: Integer}
57-
deriving stock (Show)
58-
5957
data Architecture
6058
= AArch64
6159
| Alpha

code/hsec-tools/src/Security/Advisories/Parse.hs

Lines changed: 23 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ module Security.Advisories.Parse
1414
)
1515
where
1616

17+
import qualified Security.CWE as CWE
1718
import Data.Bifunctor (first)
1819
import Data.Foldable (toList)
1920
import Data.List (intercalate)
@@ -25,6 +26,7 @@ import GHC.Generics (Generic)
2526
import qualified Data.Map as Map
2627
import Data.Sequence (Seq((:<|)))
2728
import qualified Data.Text as T
29+
import qualified Data.Text.Read as T
2830
import qualified Data.Text.Lazy as T (toStrict)
2931
import Data.Time (ZonedTime(..), LocalTime (LocalTime), midnight, utc)
3032
import Distribution.Parsec (eitherParsec)
@@ -222,7 +224,7 @@ data AdvisoryMetadata = AdvisoryMetadata
222224
{ amdId :: HsecId
223225
, amdModified :: Maybe ZonedTime
224226
, amdPublished :: Maybe ZonedTime
225-
, amdCWEs :: [CWE]
227+
, amdCWEs :: [CWE.CWEID]
226228
, amdKeywords :: [Keyword]
227229
, amdAliases :: [T.Text]
228230
, amdRelated :: [T.Text]
@@ -321,11 +323,26 @@ instance Toml.FromValue HsecId where
321323
instance Toml.ToValue HsecId where
322324
toValue = Toml.toValue . printHsecId
323325

324-
instance Toml.FromValue CWE where
325-
fromValue v = CWE <$> Toml.fromValue v
326-
327-
instance Toml.ToValue CWE where
328-
toValue (CWE x) = Toml.toValue x
326+
instance Toml.FromValue CWE.CWEID where
327+
fromValue v = case v of
328+
-- Check if the cwe number is known
329+
Toml.Integer int | Just cwe <- CWE.mkCWEID int, Map.member cwe CWE.cweNames -> pure cwe
330+
-- Check if the cwe text match "number: description"
331+
Toml.String string -> case T.breakOn ":" (T.pack string) of
332+
(numTxt, name) -> case T.decimal numTxt of
333+
Right (num, "") -> do
334+
-- Value is a "num: text", now validate if it's known
335+
cwe <- Toml.fromValue (Toml.Integer num)
336+
case T.strip (T.drop 1 name) of
337+
"" -> pure cwe
338+
expectedName -> case Map.lookup cwe CWE.cweNames of
339+
Just cweName | expectedName == cweName -> pure cwe
340+
_ -> fail ("unexpected description, got: " <> show cwe <> ", expected: " <> show expectedName)
341+
_ -> fail ("expected a number, got: " <> show numTxt)
342+
_ -> fail "expected a valid number or a cwe text description"
343+
344+
instance Toml.ToValue CWE.CWEID where
345+
toValue = Toml.toValue . CWE.unCWEID
329346

330347
instance Toml.FromValue Keyword where
331348
fromValue v = Keyword <$> Toml.fromValue v

0 commit comments

Comments
 (0)