Skip to content

Commit

Permalink
Update hsec-tool to use the new CWE data and validation
Browse files Browse the repository at this point in the history
  • Loading branch information
TristanCacqueray committed Dec 13, 2023
1 parent 43bd750 commit 0c68096
Show file tree
Hide file tree
Showing 7 changed files with 37 additions and 15 deletions.
1 change: 1 addition & 0 deletions .github/workflows/haskell-ci.yml
Original file line number Diff line number Diff line change
Expand Up @@ -183,6 +183,7 @@ jobs:
touch cabal.project
echo "packages: $GITHUB_WORKSPACE/source/code/hsec-tools" >> cabal.project
echo "packages: $GITHUB_WORKSPACE/source/code/cvss" >> cabal.project
echo "packages: $GITHUB_WORKSPACE/source/code/cwe" >> cabal.project
cat cabal.project
- name: sdist
run: |
Expand Down
1 change: 1 addition & 0 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -2,3 +2,4 @@ packages: code/*/*.cabal

package hsec-tools
package cvss
package cwe
6 changes: 5 additions & 1 deletion code/cwe/src/Security/CWE.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
module Security.CWE (CWEID, mkCWEID, cweNames, cweIds) where
module Security.CWE (CWEID, unCWEID, mkCWEID, cweNames, cweIds) where

import Security.CWE.Data
import Data.Text (Text)
Expand All @@ -14,6 +14,10 @@ import Data.Bits
newtype CWEID = CWEID Word
deriving newtype (Eq, Ord, Show)

-- | Access the underlying data.
unCWEID :: CWEID -> Word
unCWEID (CWEID cwe) = cwe

mkCWEID :: (Integral a, Bits a) => a -> Maybe CWEID
mkCWEID num = CWEID <$> toIntegralSized num

Expand Down
3 changes: 2 additions & 1 deletion code/hsec-tools/hsec-tools.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,8 @@ library
, commonmark ^>=0.2.2
, commonmark-pandoc >=0.2 && <0.3
, containers >=0.6 && <0.7
, cvss
, cvss >=0.1 && <2
, cwe >=0.1 && <2
, directory <2
, extra ^>=1.7.5
, filepath >=1.4 && <1.5
Expand Down
8 changes: 3 additions & 5 deletions code/hsec-tools/src/Security/Advisories/Definition.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,14 +4,15 @@ module Security.Advisories.Definition
( Advisory(..)
-- * Supporting types
, Affected(..)
, CWE(..)
, CWEID
, Architecture(..)
, AffectedVersionRange(..)
, OS(..)
, Keyword(..)
)
where

import Security.CWE (CWEID)
import Data.Text (Text)
import Data.Time (ZonedTime)
import Distribution.Types.Version (Version)
Expand All @@ -27,7 +28,7 @@ data Advisory = Advisory
{ advisoryId :: HsecId
, advisoryModified :: ZonedTime
, advisoryPublished :: ZonedTime
, advisoryCWEs :: [CWE]
, advisoryCWEs :: [CWEID]
, advisoryKeywords :: [Keyword]
, advisoryAliases :: [Text]
, advisoryRelated :: [Text]
Expand All @@ -54,9 +55,6 @@ data Affected = Affected
}
deriving stock (Show)

newtype CWE = CWE {unCWE :: Integer}
deriving stock (Show)

data Architecture
= AArch64
| Alpha
Expand Down
29 changes: 23 additions & 6 deletions code/hsec-tools/src/Security/Advisories/Parse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ module Security.Advisories.Parse
)
where

import qualified Security.CWE as CWE
import Data.Bifunctor (first)
import Data.Foldable (toList)
import Data.List (intercalate)
Expand All @@ -25,6 +26,7 @@ import GHC.Generics (Generic)
import qualified Data.Map as Map
import Data.Sequence (Seq((:<|)))
import qualified Data.Text as T
import qualified Data.Text.Read as T
import qualified Data.Text.Lazy as T (toStrict)
import Data.Time (ZonedTime(..), LocalTime (LocalTime), midnight, utc)
import Distribution.Parsec (eitherParsec)
Expand Down Expand Up @@ -223,7 +225,7 @@ data AdvisoryMetadata = AdvisoryMetadata
{ amdId :: HsecId
, amdModified :: Maybe ZonedTime
, amdPublished :: Maybe ZonedTime
, amdCWEs :: [CWE]
, amdCWEs :: [CWE.CWEID]
, amdKeywords :: [Keyword]
, amdAliases :: [T.Text]
, amdRelated :: [T.Text]
Expand Down Expand Up @@ -322,11 +324,26 @@ instance Toml.FromValue HsecId where
instance Toml.ToValue HsecId where
toValue = Toml.toValue . printHsecId

instance Toml.FromValue CWE where
fromValue v = CWE <$> Toml.fromValue v

instance Toml.ToValue CWE where
toValue (CWE x) = Toml.toValue x
instance Toml.FromValue CWE.CWEID where
fromValue v = case v of
-- Check if the cwe number is known
Toml.Integer int | Just cwe <- CWE.mkCWEID int, Map.member cwe CWE.cweNames -> pure cwe
-- Check if the cwe text match "number: description"
Toml.String string -> case T.breakOn ":" (T.pack string) of
(numTxt, name) -> case T.decimal numTxt of
Right (num, "") -> do
-- Value is a "num: text", now validate if it's known
cwe <- Toml.fromValue (Toml.Integer num)
case T.strip (T.drop 1 name) of
"" -> pure cwe
expectedName -> case Map.lookup cwe CWE.cweNames of
Just cweName | expectedName == cweName -> pure cwe
_ -> fail ("unexpected description, got: " <> show cwe <> ", expected: " <> show expectedName)
_ -> fail ("expected a number, got: " <> show numTxt)
_ -> fail "expected a valid number or a cwe text description"

instance Toml.ToValue CWE.CWEID where
toValue = Toml.toValue . CWE.unCWEID

instance Toml.FromValue Keyword where
fromValue v = Keyword <$> Toml.fromValue v
Expand Down
4 changes: 2 additions & 2 deletions flake.nix
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@
pkgs.haskell.lib.doJailbreak (pkgs.haskell.lib.dontCheck (pkgs.haskell.lib.unmarkBroken pkg));

cvss = pkgs.haskellPackages.callCabal2nix "cvss" ./code/cvss {};
cwe = pkgs.haskellPackages.callCabal2nix "cwe" ./code/cwe {};

hsec-tools = returnShellEnv:
pkgs.haskellPackages.developPackage {
Expand All @@ -28,10 +29,9 @@
root = ./code/hsec-tools;
withHoogle = false;
overrides = self: super: {
inherit cvss;
inherit cvss cwe;
Cabal-syntax = super.Cabal-syntax_3_8_1_0;
toml-parser = jailbreakUnbreak (super.callCabal2nix "toml-parser" toml-parser { });
cwe = super.callCabal2nix "cwe" ./code/cwe {};
};

modifier = drv:
Expand Down

0 comments on commit 0c68096

Please sign in to comment.