{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
module Security.OSV
(
Model(..)
, newModel
, newModel'
, defaultSchemaVersion
, Affected(..)
, Credit(..)
, CreditType(..)
, creditTypes
, Event(..)
, Package(..)
, Range(..)
, Reference(..)
, ReferenceType(..)
, referenceTypes
, Severity(..)
)
where
import Control.Applicative ((<|>))
import Control.Monad (when)
import Data.Maybe (catMaybes, fromMaybe)
import Data.Aeson
( ToJSON(..), FromJSON(..), Value(..)
, (.:), (.:?), (.=), object, withObject, withText
)
import Data.Aeson.Types
( Key, Object, Parser
, explicitParseField, explicitParseFieldMaybe, prependFailure, typeMismatch
)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Time (UTCTime)
import Data.Time.Format.ISO8601 (iso8601ParseM)
import Data.Tuple (swap)
import qualified Security.CVSS as CVSS
data Affected dbSpecific ecosystemSpecific rangeDbSpecific = Affected
{ forall dbSpecific ecosystemSpecific rangeDbSpecific.
Affected dbSpecific ecosystemSpecific rangeDbSpecific
-> [Range rangeDbSpecific]
affectedRanges :: [Range rangeDbSpecific]
, forall dbSpecific ecosystemSpecific rangeDbSpecific.
Affected dbSpecific ecosystemSpecific rangeDbSpecific -> Package
affectedPackage :: Package
, forall dbSpecific ecosystemSpecific rangeDbSpecific.
Affected dbSpecific ecosystemSpecific rangeDbSpecific -> [Severity]
affectedSeverity :: [Severity]
, forall dbSpecific ecosystemSpecific rangeDbSpecific.
Affected dbSpecific ecosystemSpecific rangeDbSpecific
-> Maybe ecosystemSpecific
affectedEcosystemSpecific :: Maybe ecosystemSpecific
, forall dbSpecific ecosystemSpecific rangeDbSpecific.
Affected dbSpecific ecosystemSpecific rangeDbSpecific
-> Maybe dbSpecific
affectedDatabaseSpecific :: Maybe dbSpecific
} deriving (Int
-> Affected dbSpecific ecosystemSpecific rangeDbSpecific -> ShowS
[Affected dbSpecific ecosystemSpecific rangeDbSpecific] -> ShowS
Affected dbSpecific ecosystemSpecific rangeDbSpecific -> String
(Int
-> Affected dbSpecific ecosystemSpecific rangeDbSpecific -> ShowS)
-> (Affected dbSpecific ecosystemSpecific rangeDbSpecific
-> String)
-> ([Affected dbSpecific ecosystemSpecific rangeDbSpecific]
-> ShowS)
-> Show (Affected dbSpecific ecosystemSpecific rangeDbSpecific)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall dbSpecific ecosystemSpecific rangeDbSpecific.
(Show rangeDbSpecific, Show ecosystemSpecific, Show dbSpecific) =>
Int
-> Affected dbSpecific ecosystemSpecific rangeDbSpecific -> ShowS
forall dbSpecific ecosystemSpecific rangeDbSpecific.
(Show rangeDbSpecific, Show ecosystemSpecific, Show dbSpecific) =>
[Affected dbSpecific ecosystemSpecific rangeDbSpecific] -> ShowS
forall dbSpecific ecosystemSpecific rangeDbSpecific.
(Show rangeDbSpecific, Show ecosystemSpecific, Show dbSpecific) =>
Affected dbSpecific ecosystemSpecific rangeDbSpecific -> String
$cshowsPrec :: forall dbSpecific ecosystemSpecific rangeDbSpecific.
(Show rangeDbSpecific, Show ecosystemSpecific, Show dbSpecific) =>
Int
-> Affected dbSpecific ecosystemSpecific rangeDbSpecific -> ShowS
showsPrec :: Int
-> Affected dbSpecific ecosystemSpecific rangeDbSpecific -> ShowS
$cshow :: forall dbSpecific ecosystemSpecific rangeDbSpecific.
(Show rangeDbSpecific, Show ecosystemSpecific, Show dbSpecific) =>
Affected dbSpecific ecosystemSpecific rangeDbSpecific -> String
show :: Affected dbSpecific ecosystemSpecific rangeDbSpecific -> String
$cshowList :: forall dbSpecific ecosystemSpecific rangeDbSpecific.
(Show rangeDbSpecific, Show ecosystemSpecific, Show dbSpecific) =>
[Affected dbSpecific ecosystemSpecific rangeDbSpecific] -> ShowS
showList :: [Affected dbSpecific ecosystemSpecific rangeDbSpecific] -> ShowS
Show, Affected dbSpecific ecosystemSpecific rangeDbSpecific
-> Affected dbSpecific ecosystemSpecific rangeDbSpecific -> Bool
(Affected dbSpecific ecosystemSpecific rangeDbSpecific
-> Affected dbSpecific ecosystemSpecific rangeDbSpecific -> Bool)
-> (Affected dbSpecific ecosystemSpecific rangeDbSpecific
-> Affected dbSpecific ecosystemSpecific rangeDbSpecific -> Bool)
-> Eq (Affected dbSpecific ecosystemSpecific rangeDbSpecific)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall dbSpecific ecosystemSpecific rangeDbSpecific.
(Eq rangeDbSpecific, Eq ecosystemSpecific, Eq dbSpecific) =>
Affected dbSpecific ecosystemSpecific rangeDbSpecific
-> Affected dbSpecific ecosystemSpecific rangeDbSpecific -> Bool
$c== :: forall dbSpecific ecosystemSpecific rangeDbSpecific.
(Eq rangeDbSpecific, Eq ecosystemSpecific, Eq dbSpecific) =>
Affected dbSpecific ecosystemSpecific rangeDbSpecific
-> Affected dbSpecific ecosystemSpecific rangeDbSpecific -> Bool
== :: Affected dbSpecific ecosystemSpecific rangeDbSpecific
-> Affected dbSpecific ecosystemSpecific rangeDbSpecific -> Bool
$c/= :: forall dbSpecific ecosystemSpecific rangeDbSpecific.
(Eq rangeDbSpecific, Eq ecosystemSpecific, Eq dbSpecific) =>
Affected dbSpecific ecosystemSpecific rangeDbSpecific
-> Affected dbSpecific ecosystemSpecific rangeDbSpecific -> Bool
/= :: Affected dbSpecific ecosystemSpecific rangeDbSpecific
-> Affected dbSpecific ecosystemSpecific rangeDbSpecific -> Bool
Eq)
data Event a
= EventIntroduced a
| EventFixed a
| EventLastAffected a
| EventLimit a
deriving (Event a -> Event a -> Bool
(Event a -> Event a -> Bool)
-> (Event a -> Event a -> Bool) -> Eq (Event a)
forall a. Eq a => Event a -> Event a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Event a -> Event a -> Bool
== :: Event a -> Event a -> Bool
$c/= :: forall a. Eq a => Event a -> Event a -> Bool
/= :: Event a -> Event a -> Bool
Eq, Eq (Event a)
Eq (Event a) =>
(Event a -> Event a -> Ordering)
-> (Event a -> Event a -> Bool)
-> (Event a -> Event a -> Bool)
-> (Event a -> Event a -> Bool)
-> (Event a -> Event a -> Bool)
-> (Event a -> Event a -> Event a)
-> (Event a -> Event a -> Event a)
-> Ord (Event a)
Event a -> Event a -> Bool
Event a -> Event a -> Ordering
Event a -> Event a -> Event a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (Event a)
forall a. Ord a => Event a -> Event a -> Bool
forall a. Ord a => Event a -> Event a -> Ordering
forall a. Ord a => Event a -> Event a -> Event a
$ccompare :: forall a. Ord a => Event a -> Event a -> Ordering
compare :: Event a -> Event a -> Ordering
$c< :: forall a. Ord a => Event a -> Event a -> Bool
< :: Event a -> Event a -> Bool
$c<= :: forall a. Ord a => Event a -> Event a -> Bool
<= :: Event a -> Event a -> Bool
$c> :: forall a. Ord a => Event a -> Event a -> Bool
> :: Event a -> Event a -> Bool
$c>= :: forall a. Ord a => Event a -> Event a -> Bool
>= :: Event a -> Event a -> Bool
$cmax :: forall a. Ord a => Event a -> Event a -> Event a
max :: Event a -> Event a -> Event a
$cmin :: forall a. Ord a => Event a -> Event a -> Event a
min :: Event a -> Event a -> Event a
Ord, Int -> Event a -> ShowS
[Event a] -> ShowS
Event a -> String
(Int -> Event a -> ShowS)
-> (Event a -> String) -> ([Event a] -> ShowS) -> Show (Event a)
forall a. Show a => Int -> Event a -> ShowS
forall a. Show a => [Event a] -> ShowS
forall a. Show a => Event a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Event a -> ShowS
showsPrec :: Int -> Event a -> ShowS
$cshow :: forall a. Show a => Event a -> String
show :: Event a -> String
$cshowList :: forall a. Show a => [Event a] -> ShowS
showList :: [Event a] -> ShowS
Show)
instance (FromJSON a) => FromJSON (Event a) where
parseJSON :: Value -> Parser (Event a)
parseJSON = String -> (Object -> Parser (Event a)) -> Value -> Parser (Event a)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"events[]" ((Object -> Parser (Event a)) -> Value -> Parser (Event a))
-> (Object -> Parser (Event a)) -> Value -> Parser (Event a)
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Bool -> Parser () -> Parser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Object -> Int
forall a. KeyMap a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Object
o Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
1) (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ String -> Value -> Parser ()
forall a. String -> Value -> Parser a
typeMismatch String
"events[]" (Object -> Value
Object Object
o)
String -> Parser (Event a) -> Parser (Event a)
forall a. String -> Parser a -> Parser a
prependFailure String
"unknown event type" (Parser (Event a) -> Parser (Event a))
-> Parser (Event a) -> Parser (Event a)
forall a b. (a -> b) -> a -> b
$
a -> Event a
forall a. a -> Event a
EventIntroduced (a -> Event a) -> Parser a -> Parser (Event a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser a
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"introduced"
Parser (Event a) -> Parser (Event a) -> Parser (Event a)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> a -> Event a
forall a. a -> Event a
EventFixed (a -> Event a) -> Parser a -> Parser (Event a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser a
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"fixed"
Parser (Event a) -> Parser (Event a) -> Parser (Event a)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> a -> Event a
forall a. a -> Event a
EventLastAffected (a -> Event a) -> Parser a -> Parser (Event a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser a
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"last_affected"
Parser (Event a) -> Parser (Event a) -> Parser (Event a)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> a -> Event a
forall a. a -> Event a
EventLimit (a -> Event a) -> Parser a -> Parser (Event a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser a
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"limit"
instance (ToJSON a) => ToJSON (Event a) where
toJSON :: Event a -> Value
toJSON Event a
ev = [Pair] -> Value
object ([Pair] -> Value) -> (Pair -> [Pair]) -> Pair -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Pair -> Value) -> Pair -> Value
forall a b. (a -> b) -> a -> b
$ case Event a
ev of
EventIntroduced a
a -> Key
"introduced" Key -> a -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= a
a
EventFixed a
a -> Key
"fixed" Key -> a -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= a
a
EventLastAffected a
a -> Key
"last_affected" Key -> a -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= a
a
EventLimit a
a -> Key
"limit" Key -> a -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= a
a
data Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific = Model
{ forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Text
modelSchemaVersion :: Text
, forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Text
modelId :: Text
, forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> UTCTime
modelModified :: UTCTime
, forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Maybe UTCTime
modelPublished :: Maybe UTCTime
, forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Maybe UTCTime
modelWithdrawn :: Maybe UTCTime
, forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> [Text]
modelAliases :: [Text]
, forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> [Text]
modelRelated :: [Text]
, forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Maybe Text
modelSummary :: Maybe Text
, forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Maybe Text
modelDetails :: Maybe Text
, forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> [Severity]
modelSeverity :: [Severity]
, forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> [Affected
affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
modelAffected :: [Affected affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
, forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> [Reference]
modelReferences :: [Reference]
, forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> [Credit]
modelCredits :: [Credit]
, forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Maybe dbSpecific
modelDatabaseSpecific :: Maybe dbSpecific
} deriving (Int
-> Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> ShowS
[Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific]
-> ShowS
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> String
(Int
-> Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> ShowS)
-> (Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> String)
-> ([Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific]
-> ShowS)
-> Show
(Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
(Show rangeDbSpecific, Show affectedDbSpecific,
Show affectedEcosystemSpecific, Show dbSpecific) =>
Int
-> Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> ShowS
forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
(Show rangeDbSpecific, Show affectedDbSpecific,
Show affectedEcosystemSpecific, Show dbSpecific) =>
[Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific]
-> ShowS
forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
(Show rangeDbSpecific, Show affectedDbSpecific,
Show affectedEcosystemSpecific, Show dbSpecific) =>
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> String
$cshowsPrec :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
(Show rangeDbSpecific, Show affectedDbSpecific,
Show affectedEcosystemSpecific, Show dbSpecific) =>
Int
-> Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> ShowS
showsPrec :: Int
-> Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> ShowS
$cshow :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
(Show rangeDbSpecific, Show affectedDbSpecific,
Show affectedEcosystemSpecific, Show dbSpecific) =>
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> String
show :: Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> String
$cshowList :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
(Show rangeDbSpecific, Show affectedDbSpecific,
Show affectedEcosystemSpecific, Show dbSpecific) =>
[Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific]
-> ShowS
showList :: [Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific]
-> ShowS
Show, Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Bool
(Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Bool)
-> (Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Bool)
-> Eq
(Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
(Eq rangeDbSpecific, Eq affectedDbSpecific,
Eq affectedEcosystemSpecific, Eq dbSpecific) =>
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Bool
$c== :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
(Eq rangeDbSpecific, Eq affectedDbSpecific,
Eq affectedEcosystemSpecific, Eq dbSpecific) =>
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Bool
== :: Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Bool
$c/= :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
(Eq rangeDbSpecific, Eq affectedDbSpecific,
Eq affectedEcosystemSpecific, Eq dbSpecific) =>
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Bool
/= :: Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Bool
Eq)
defaultSchemaVersion :: Text
defaultSchemaVersion :: Text
defaultSchemaVersion = Text
"1.5.0"
newModel
:: Text
-> Text
-> UTCTime
-> Model dbs aes adbs rdbs
newModel :: forall dbs aes adbs rdbs.
Text -> Text -> UTCTime -> Model dbs aes adbs rdbs
newModel Text
ver Text
ident UTCTime
modified = Text
-> Text
-> UTCTime
-> Maybe UTCTime
-> Maybe UTCTime
-> [Text]
-> [Text]
-> Maybe Text
-> Maybe Text
-> [Severity]
-> [Affected aes adbs rdbs]
-> [Reference]
-> [Credit]
-> Maybe dbs
-> Model dbs aes adbs rdbs
forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Text
-> Text
-> UTCTime
-> Maybe UTCTime
-> Maybe UTCTime
-> [Text]
-> [Text]
-> Maybe Text
-> Maybe Text
-> [Severity]
-> [Affected
affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
-> [Reference]
-> [Credit]
-> Maybe dbSpecific
-> Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
Model
Text
ver
Text
ident
UTCTime
modified
Maybe UTCTime
forall a. Maybe a
Nothing
Maybe UTCTime
forall a. Maybe a
Nothing
[]
[]
Maybe Text
forall a. Maybe a
Nothing
Maybe Text
forall a. Maybe a
Nothing
[]
[]
[]
[]
Maybe dbs
forall a. Maybe a
Nothing
newModel'
:: Text
-> UTCTime
-> Model dbs aes adbs rdbs
newModel' :: forall dbs aes adbs rdbs.
Text -> UTCTime -> Model dbs aes adbs rdbs
newModel' = Text -> Text -> UTCTime -> Model dbs aes adbs rdbs
forall dbs aes adbs rdbs.
Text -> Text -> UTCTime -> Model dbs aes adbs rdbs
newModel Text
defaultSchemaVersion
newtype Severity = Severity CVSS.CVSS
deriving (Int -> Severity -> ShowS
[Severity] -> ShowS
Severity -> String
(Int -> Severity -> ShowS)
-> (Severity -> String) -> ([Severity] -> ShowS) -> Show Severity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Severity -> ShowS
showsPrec :: Int -> Severity -> ShowS
$cshow :: Severity -> String
show :: Severity -> String
$cshowList :: [Severity] -> ShowS
showList :: [Severity] -> ShowS
Show)
instance Eq Severity where
Severity CVSS
s1 == :: Severity -> Severity -> Bool
== Severity CVSS
s2 = CVSS -> Text
CVSS.cvssVectorString CVSS
s1 Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== CVSS -> Text
CVSS.cvssVectorString CVSS
s2
instance FromJSON Severity where
parseJSON :: Value -> Parser Severity
parseJSON = String -> (Object -> Parser Severity) -> Value -> Parser Severity
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"severity" ((Object -> Parser Severity) -> Value -> Parser Severity)
-> (Object -> Parser Severity) -> Value -> Parser Severity
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Text
typ <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type" :: Parser Text
Text
score <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"score" :: Parser Text
CVSS
cvss <- case Text -> Either CVSSError CVSS
CVSS.parseCVSS Text
score of
Right CVSS
cvss -> CVSS -> Parser CVSS
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure CVSS
cvss
Left CVSSError
err ->
String -> Parser CVSS -> Parser CVSS
forall a. String -> Parser a -> Parser a
prependFailure (String
"unregognised severity score: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> CVSSError -> String
forall a. Show a => a -> String
show CVSSError
err)
(Parser CVSS -> Parser CVSS) -> Parser CVSS -> Parser CVSS
forall a b. (a -> b) -> a -> b
$ String -> Value -> Parser CVSS
forall a. String -> Value -> Parser a
typeMismatch String
"severity" (Object -> Value
Object Object
o)
case Text
typ of
Text
"CVSS_V2" | CVSS -> CVSSVersion
CVSS.cvssVersion CVSS
cvss CVSSVersion -> CVSSVersion -> Bool
forall a. Eq a => a -> a -> Bool
== CVSSVersion
CVSS.CVSS20 -> Severity -> Parser Severity
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Severity -> Parser Severity) -> Severity -> Parser Severity
forall a b. (a -> b) -> a -> b
$ CVSS -> Severity
Severity CVSS
cvss
Text
"CVSS_V3" | CVSS -> CVSSVersion
CVSS.cvssVersion CVSS
cvss CVSSVersion -> [CVSSVersion] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [CVSSVersion
CVSS.CVSS30, CVSSVersion
CVSS.CVSS31] -> Severity -> Parser Severity
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Severity -> Parser Severity) -> Severity -> Parser Severity
forall a b. (a -> b) -> a -> b
$ CVSS -> Severity
Severity CVSS
cvss
Text
s ->
String -> Parser Severity -> Parser Severity
forall a. String -> Parser a -> Parser a
prependFailure (String
"unregognised severity type: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
forall a. Show a => a -> String
show Text
s)
(Parser Severity -> Parser Severity)
-> Parser Severity -> Parser Severity
forall a b. (a -> b) -> a -> b
$ String -> Value -> Parser Severity
forall a. String -> Value -> Parser a
typeMismatch String
"severity" (Object -> Value
Object Object
o)
instance ToJSON Severity where
toJSON :: Severity -> Value
toJSON (Severity CVSS
cvss) = [Pair] -> Value
object [Key
"score" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= CVSS -> Text
CVSS.cvssVectorString CVSS
cvss, Key
"type" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
typ]
where
typ :: Text
typ :: Text
typ = case CVSS -> CVSSVersion
CVSS.cvssVersion CVSS
cvss of
CVSSVersion
CVSS.CVSS31 -> Text
"CVSS_V3"
CVSSVersion
CVSS.CVSS30 -> Text
"CVSS_V3"
CVSSVersion
CVSS.CVSS20 -> Text
"CVSS_V2"
data Package = Package
{ Package -> Text
packageName :: Text
, Package -> Text
packageEcosystem :: Text
, Package -> Maybe Text
packagePurl :: Maybe Text
} deriving (Int -> Package -> ShowS
[Package] -> ShowS
Package -> String
(Int -> Package -> ShowS)
-> (Package -> String) -> ([Package] -> ShowS) -> Show Package
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Package -> ShowS
showsPrec :: Int -> Package -> ShowS
$cshow :: Package -> String
show :: Package -> String
$cshowList :: [Package] -> ShowS
showList :: [Package] -> ShowS
Show, Package -> Package -> Bool
(Package -> Package -> Bool)
-> (Package -> Package -> Bool) -> Eq Package
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Package -> Package -> Bool
== :: Package -> Package -> Bool
$c/= :: Package -> Package -> Bool
/= :: Package -> Package -> Bool
Eq, Eq Package
Eq Package =>
(Package -> Package -> Ordering)
-> (Package -> Package -> Bool)
-> (Package -> Package -> Bool)
-> (Package -> Package -> Bool)
-> (Package -> Package -> Bool)
-> (Package -> Package -> Package)
-> (Package -> Package -> Package)
-> Ord Package
Package -> Package -> Bool
Package -> Package -> Ordering
Package -> Package -> Package
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Package -> Package -> Ordering
compare :: Package -> Package -> Ordering
$c< :: Package -> Package -> Bool
< :: Package -> Package -> Bool
$c<= :: Package -> Package -> Bool
<= :: Package -> Package -> Bool
$c> :: Package -> Package -> Bool
> :: Package -> Package -> Bool
$c>= :: Package -> Package -> Bool
>= :: Package -> Package -> Bool
$cmax :: Package -> Package -> Package
max :: Package -> Package -> Package
$cmin :: Package -> Package -> Package
min :: Package -> Package -> Package
Ord)
data Range dbSpecific
= RangeSemVer [Event Text ] (Maybe dbSpecific)
| RangeEcosystem [Event Text] (Maybe dbSpecific)
| RangeGit
[Event Text ]
Text
(Maybe dbSpecific)
deriving (Range dbSpecific -> Range dbSpecific -> Bool
(Range dbSpecific -> Range dbSpecific -> Bool)
-> (Range dbSpecific -> Range dbSpecific -> Bool)
-> Eq (Range dbSpecific)
forall dbSpecific.
Eq dbSpecific =>
Range dbSpecific -> Range dbSpecific -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall dbSpecific.
Eq dbSpecific =>
Range dbSpecific -> Range dbSpecific -> Bool
== :: Range dbSpecific -> Range dbSpecific -> Bool
$c/= :: forall dbSpecific.
Eq dbSpecific =>
Range dbSpecific -> Range dbSpecific -> Bool
/= :: Range dbSpecific -> Range dbSpecific -> Bool
Eq, Int -> Range dbSpecific -> ShowS
[Range dbSpecific] -> ShowS
Range dbSpecific -> String
(Int -> Range dbSpecific -> ShowS)
-> (Range dbSpecific -> String)
-> ([Range dbSpecific] -> ShowS)
-> Show (Range dbSpecific)
forall dbSpecific.
Show dbSpecific =>
Int -> Range dbSpecific -> ShowS
forall dbSpecific. Show dbSpecific => [Range dbSpecific] -> ShowS
forall dbSpecific. Show dbSpecific => Range dbSpecific -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall dbSpecific.
Show dbSpecific =>
Int -> Range dbSpecific -> ShowS
showsPrec :: Int -> Range dbSpecific -> ShowS
$cshow :: forall dbSpecific. Show dbSpecific => Range dbSpecific -> String
show :: Range dbSpecific -> String
$cshowList :: forall dbSpecific. Show dbSpecific => [Range dbSpecific] -> ShowS
showList :: [Range dbSpecific] -> ShowS
Show)
instance (FromJSON dbSpecific) => FromJSON (Range dbSpecific) where
parseJSON :: Value -> Parser (Range dbSpecific)
parseJSON = String
-> (Object -> Parser (Range dbSpecific))
-> Value
-> Parser (Range dbSpecific)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ranges[]" ((Object -> Parser (Range dbSpecific))
-> Value -> Parser (Range dbSpecific))
-> (Object -> Parser (Range dbSpecific))
-> Value
-> Parser (Range dbSpecific)
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Text
typ <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type" :: Parser Text
case Text
typ of
Text
"SEMVER" -> [Event Text] -> Maybe dbSpecific -> Range dbSpecific
forall dbSpecific.
[Event Text] -> Maybe dbSpecific -> Range dbSpecific
RangeSemVer ([Event Text] -> Maybe dbSpecific -> Range dbSpecific)
-> Parser [Event Text]
-> Parser (Maybe dbSpecific -> Range dbSpecific)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser [Event Text]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"events" Parser (Maybe dbSpecific -> Range dbSpecific)
-> Parser (Maybe dbSpecific) -> Parser (Range dbSpecific)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe dbSpecific)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"database_specific"
Text
"ECOSYSTEM" -> [Event Text] -> Maybe dbSpecific -> Range dbSpecific
forall dbSpecific.
[Event Text] -> Maybe dbSpecific -> Range dbSpecific
RangeEcosystem ([Event Text] -> Maybe dbSpecific -> Range dbSpecific)
-> Parser [Event Text]
-> Parser (Maybe dbSpecific -> Range dbSpecific)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser [Event Text]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"events" Parser (Maybe dbSpecific -> Range dbSpecific)
-> Parser (Maybe dbSpecific) -> Parser (Range dbSpecific)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe dbSpecific)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"database_specific"
Text
"GIT" -> [Event Text] -> Text -> Maybe dbSpecific -> Range dbSpecific
forall dbSpecific.
[Event Text] -> Text -> Maybe dbSpecific -> Range dbSpecific
RangeGit ([Event Text] -> Text -> Maybe dbSpecific -> Range dbSpecific)
-> Parser [Event Text]
-> Parser (Text -> Maybe dbSpecific -> Range dbSpecific)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser [Event Text]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"events" Parser (Text -> Maybe dbSpecific -> Range dbSpecific)
-> Parser Text -> Parser (Maybe dbSpecific -> Range dbSpecific)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"repo" Parser (Maybe dbSpecific -> Range dbSpecific)
-> Parser (Maybe dbSpecific) -> Parser (Range dbSpecific)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe dbSpecific)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"database_specific"
Text
s ->
String -> Parser (Range dbSpecific) -> Parser (Range dbSpecific)
forall a. String -> Parser a -> Parser a
prependFailure (String
"unregognised range type: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
forall a. Show a => a -> String
show Text
s)
(Parser (Range dbSpecific) -> Parser (Range dbSpecific))
-> Parser (Range dbSpecific) -> Parser (Range dbSpecific)
forall a b. (a -> b) -> a -> b
$ String -> Value -> Parser (Range dbSpecific)
forall a. String -> Value -> Parser a
typeMismatch String
"ranges[]" (Object -> Value
Object Object
o)
instance (ToJSON dbSpecific) => ToJSON (Range dbSpecific) where
toJSON :: Range dbSpecific -> Value
toJSON Range dbSpecific
range = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ case Range dbSpecific
range of
RangeSemVer [Event Text]
evs Maybe dbSpecific
dbs -> [Text -> Pair
forall {e} {kv}. KeyValue e kv => Text -> kv
typ Text
"SEMVER", Key
"events" Key -> [Event Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Event Text]
evs] [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> Maybe dbSpecific -> [Pair]
mkDbSpecific Maybe dbSpecific
dbs
RangeEcosystem [Event Text]
evs Maybe dbSpecific
dbs -> [Text -> Pair
forall {e} {kv}. KeyValue e kv => Text -> kv
typ Text
"ECOSYSTEM", Key
"events" Key -> [Event Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Event Text]
evs] [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> Maybe dbSpecific -> [Pair]
mkDbSpecific Maybe dbSpecific
dbs
RangeGit [Event Text]
evs Text
repo Maybe dbSpecific
dbs -> [Text -> Pair
forall {e} {kv}. KeyValue e kv => Text -> kv
typ Text
"GIT", Key
"events" Key -> [Event Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Event Text]
evs, Key
"repo" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
repo] [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> Maybe dbSpecific -> [Pair]
mkDbSpecific Maybe dbSpecific
dbs
where
mkDbSpecific :: Maybe dbSpecific -> [Pair]
mkDbSpecific = [Pair] -> (dbSpecific -> [Pair]) -> Maybe dbSpecific -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\dbSpecific
v -> [Key
"database_specific" Key -> dbSpecific -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= dbSpecific
v])
typ :: Text -> kv
typ Text
s = Key
"type" Key -> Text -> kv
forall v. ToJSON v => Key -> v -> kv
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= (Text
s :: Text)
data ReferenceType
= ReferenceTypeAdvisory
| ReferenceTypeArticle
| ReferenceTypeDetection
| ReferenceTypeDiscussion
| ReferenceTypeReport
| ReferenceTypeFix
| ReferenceTypeIntroduced
| ReferenceTypePackage
| ReferenceTypeEvidence
| ReferenceTypeWeb
deriving (Int -> ReferenceType -> ShowS
[ReferenceType] -> ShowS
ReferenceType -> String
(Int -> ReferenceType -> ShowS)
-> (ReferenceType -> String)
-> ([ReferenceType] -> ShowS)
-> Show ReferenceType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReferenceType -> ShowS
showsPrec :: Int -> ReferenceType -> ShowS
$cshow :: ReferenceType -> String
show :: ReferenceType -> String
$cshowList :: [ReferenceType] -> ShowS
showList :: [ReferenceType] -> ShowS
Show, ReferenceType -> ReferenceType -> Bool
(ReferenceType -> ReferenceType -> Bool)
-> (ReferenceType -> ReferenceType -> Bool) -> Eq ReferenceType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReferenceType -> ReferenceType -> Bool
== :: ReferenceType -> ReferenceType -> Bool
$c/= :: ReferenceType -> ReferenceType -> Bool
/= :: ReferenceType -> ReferenceType -> Bool
Eq)
referenceTypes :: [(ReferenceType, Text)]
referenceTypes :: [(ReferenceType, Text)]
referenceTypes =
[ (ReferenceType
ReferenceTypeAdvisory , Text
"ADVISORY")
, (ReferenceType
ReferenceTypeArticle , Text
"ARTICLE")
, (ReferenceType
ReferenceTypeDetection , Text
"DETECTION")
, (ReferenceType
ReferenceTypeDiscussion , Text
"DISCUSSION")
, (ReferenceType
ReferenceTypeReport , Text
"REPORT")
, (ReferenceType
ReferenceTypeFix , Text
"FIX")
, (ReferenceType
ReferenceTypeIntroduced , Text
"INTRODUCED")
, (ReferenceType
ReferenceTypePackage , Text
"PACKAGE")
, (ReferenceType
ReferenceTypeEvidence , Text
"EVIDENCE")
, (ReferenceType
ReferenceTypeWeb , Text
"WEB")
]
instance FromJSON ReferenceType where
parseJSON :: Value -> Parser ReferenceType
parseJSON = String
-> (Text -> Parser ReferenceType) -> Value -> Parser ReferenceType
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"references.type" ((Text -> Parser ReferenceType) -> Value -> Parser ReferenceType)
-> (Text -> Parser ReferenceType) -> Value -> Parser ReferenceType
forall a b. (a -> b) -> a -> b
$ \Text
s ->
case Text -> [(Text, ReferenceType)] -> Maybe ReferenceType
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
s (((ReferenceType, Text) -> (Text, ReferenceType))
-> [(ReferenceType, Text)] -> [(Text, ReferenceType)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ReferenceType, Text) -> (Text, ReferenceType)
forall a b. (a, b) -> (b, a)
swap [(ReferenceType, Text)]
referenceTypes) of
Just ReferenceType
v -> ReferenceType -> Parser ReferenceType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ReferenceType
v
Maybe ReferenceType
Nothing -> String -> Value -> Parser ReferenceType
forall a. String -> Value -> Parser a
typeMismatch String
"references.type" (Text -> Value
String Text
s)
instance ToJSON ReferenceType where
toJSON :: ReferenceType -> Value
toJSON ReferenceType
v = Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"WEB" (ReferenceType -> [(ReferenceType, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup ReferenceType
v [(ReferenceType, Text)]
referenceTypes)
data Reference = Reference
{ Reference -> ReferenceType
referencesType :: ReferenceType
, Reference -> Text
referencesUrl :: Text
} deriving (Int -> Reference -> ShowS
[Reference] -> ShowS
Reference -> String
(Int -> Reference -> ShowS)
-> (Reference -> String)
-> ([Reference] -> ShowS)
-> Show Reference
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Reference -> ShowS
showsPrec :: Int -> Reference -> ShowS
$cshow :: Reference -> String
show :: Reference -> String
$cshowList :: [Reference] -> ShowS
showList :: [Reference] -> ShowS
Show, Reference -> Reference -> Bool
(Reference -> Reference -> Bool)
-> (Reference -> Reference -> Bool) -> Eq Reference
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Reference -> Reference -> Bool
== :: Reference -> Reference -> Bool
$c/= :: Reference -> Reference -> Bool
/= :: Reference -> Reference -> Bool
Eq)
data CreditType
= CreditTypeFinder
| CreditTypeReporter
| CreditTypeAnalyst
| CreditTypeCoordinator
| CreditTypeRemediationDeveloper
| CreditTypeRemediationReviewer
| CreditTypeRemediationVerifier
| CreditTypeTool
|
| CreditTypeOther
deriving (Int -> CreditType -> ShowS
[CreditType] -> ShowS
CreditType -> String
(Int -> CreditType -> ShowS)
-> (CreditType -> String)
-> ([CreditType] -> ShowS)
-> Show CreditType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CreditType -> ShowS
showsPrec :: Int -> CreditType -> ShowS
$cshow :: CreditType -> String
show :: CreditType -> String
$cshowList :: [CreditType] -> ShowS
showList :: [CreditType] -> ShowS
Show, CreditType -> CreditType -> Bool
(CreditType -> CreditType -> Bool)
-> (CreditType -> CreditType -> Bool) -> Eq CreditType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CreditType -> CreditType -> Bool
== :: CreditType -> CreditType -> Bool
$c/= :: CreditType -> CreditType -> Bool
/= :: CreditType -> CreditType -> Bool
Eq)
creditTypes :: [(CreditType, Text)]
creditTypes :: [(CreditType, Text)]
creditTypes =
[ (CreditType
CreditTypeFinder , Text
"FINDER")
, (CreditType
CreditTypeReporter , Text
"REPORTER")
, (CreditType
CreditTypeAnalyst , Text
"ANALYST")
, (CreditType
CreditTypeCoordinator , Text
"COORDINATOR")
, (CreditType
CreditTypeRemediationDeveloper , Text
"REMEDIATION_DEVELOPER")
, (CreditType
CreditTypeRemediationReviewer , Text
"REMEDIATION_REVIEWER")
, (CreditType
CreditTypeRemediationVerifier , Text
"REMEDIATION_VERIFIER")
, (CreditType
CreditTypeTool , Text
"TOOL")
, (CreditType
CreditTypeSponsor , Text
"SPONSOR")
, (CreditType
CreditTypeOther , Text
"OTHER")
]
instance FromJSON CreditType where
parseJSON :: Value -> Parser CreditType
parseJSON = String -> (Text -> Parser CreditType) -> Value -> Parser CreditType
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"credits[].type" ((Text -> Parser CreditType) -> Value -> Parser CreditType)
-> (Text -> Parser CreditType) -> Value -> Parser CreditType
forall a b. (a -> b) -> a -> b
$ \Text
s ->
case Text -> [(Text, CreditType)] -> Maybe CreditType
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
s (((CreditType, Text) -> (Text, CreditType))
-> [(CreditType, Text)] -> [(Text, CreditType)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (CreditType, Text) -> (Text, CreditType)
forall a b. (a, b) -> (b, a)
swap [(CreditType, Text)]
creditTypes) of
Just CreditType
v -> CreditType -> Parser CreditType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure CreditType
v
Maybe CreditType
Nothing -> String -> Value -> Parser CreditType
forall a. String -> Value -> Parser a
typeMismatch String
"credits[].type" (Text -> Value
String Text
s)
instance ToJSON CreditType where
toJSON :: CreditType -> Value
toJSON CreditType
v = Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"OTHER" (CreditType -> [(CreditType, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup CreditType
v [(CreditType, Text)]
creditTypes)
data Credit = Credit
{ Credit -> CreditType
creditType :: CreditType
, Credit -> Text
creditName :: Text
, Credit -> [Text]
creditContacts :: [Text]
}
deriving (Int -> Credit -> ShowS
[Credit] -> ShowS
Credit -> String
(Int -> Credit -> ShowS)
-> (Credit -> String) -> ([Credit] -> ShowS) -> Show Credit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Credit -> ShowS
showsPrec :: Int -> Credit -> ShowS
$cshow :: Credit -> String
show :: Credit -> String
$cshowList :: [Credit] -> ShowS
showList :: [Credit] -> ShowS
Show, Credit -> Credit -> Bool
(Credit -> Credit -> Bool)
-> (Credit -> Credit -> Bool) -> Eq Credit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Credit -> Credit -> Bool
== :: Credit -> Credit -> Bool
$c/= :: Credit -> Credit -> Bool
/= :: Credit -> Credit -> Bool
Eq)
instance FromJSON Credit where
parseJSON :: Value -> Parser Credit
parseJSON = String -> (Object -> Parser Credit) -> Value -> Parser Credit
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"credits[]" ((Object -> Parser Credit) -> Value -> Parser Credit)
-> (Object -> Parser Credit) -> Value -> Parser Credit
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
CreditType
creditType <- Object
o Object -> Key -> Parser CreditType
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Text
creditName <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
[Text]
creditContacts <- Object
o Object -> Key -> Parser [Text]
forall a. FromJSON a => Object -> Key -> Parser [a]
.::? Key
"contact"
Credit -> Parser Credit
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Credit -> Parser Credit) -> Credit -> Parser Credit
forall a b. (a -> b) -> a -> b
$ Credit{[Text]
Text
CreditType
$sel:creditType:Credit :: CreditType
$sel:creditName:Credit :: Text
$sel:creditContacts:Credit :: [Text]
creditType :: CreditType
creditName :: Text
creditContacts :: [Text]
..}
instance ToJSON Credit where
toJSON :: Credit -> Value
toJSON Credit{[Text]
Text
CreditType
$sel:creditType:Credit :: Credit -> CreditType
$sel:creditName:Credit :: Credit -> Text
$sel:creditContacts:Credit :: Credit -> [Text]
creditType :: CreditType
creditName :: Text
creditContacts :: [Text]
..} = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"type" Key -> CreditType -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= CreditType
creditType
, Key
"name" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
creditName
]
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> Key -> [Text] -> [Pair]
forall {e} {a} {a}. (KeyValue e a, ToJSON a) => Key -> [a] -> [a]
omitEmptyList Key
"contact" [Text]
creditContacts
where
omitEmptyList :: Key -> [a] -> [a]
omitEmptyList Key
_ [] = []
omitEmptyList Key
k [a]
xs = [Key
k Key -> [a] -> a
forall v. ToJSON v => Key -> v -> a
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [a]
xs]
instance
(ToJSON ecosystemSpecific, ToJSON dbSpecific, ToJSON rangeDbSpecific)
=> ToJSON (Affected ecosystemSpecific dbSpecific rangeDbSpecific) where
toJSON :: Affected ecosystemSpecific dbSpecific rangeDbSpecific -> Value
toJSON Affected{[Range rangeDbSpecific]
[Severity]
Maybe ecosystemSpecific
Maybe dbSpecific
Package
$sel:affectedRanges:Affected :: forall dbSpecific ecosystemSpecific rangeDbSpecific.
Affected dbSpecific ecosystemSpecific rangeDbSpecific
-> [Range rangeDbSpecific]
$sel:affectedPackage:Affected :: forall dbSpecific ecosystemSpecific rangeDbSpecific.
Affected dbSpecific ecosystemSpecific rangeDbSpecific -> Package
$sel:affectedSeverity:Affected :: forall dbSpecific ecosystemSpecific rangeDbSpecific.
Affected dbSpecific ecosystemSpecific rangeDbSpecific -> [Severity]
$sel:affectedEcosystemSpecific:Affected :: forall dbSpecific ecosystemSpecific rangeDbSpecific.
Affected dbSpecific ecosystemSpecific rangeDbSpecific
-> Maybe ecosystemSpecific
$sel:affectedDatabaseSpecific:Affected :: forall dbSpecific ecosystemSpecific rangeDbSpecific.
Affected dbSpecific ecosystemSpecific rangeDbSpecific
-> Maybe dbSpecific
affectedRanges :: [Range rangeDbSpecific]
affectedPackage :: Package
affectedSeverity :: [Severity]
affectedEcosystemSpecific :: Maybe dbSpecific
affectedDatabaseSpecific :: Maybe ecosystemSpecific
..} = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"ranges" Key -> [Range rangeDbSpecific] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Range rangeDbSpecific]
affectedRanges
, Key
"package" Key -> Package -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Package
affectedPackage
]
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> Key -> [Severity] -> [Pair]
forall {e} {a} {a}. (KeyValue e a, ToJSON a) => Key -> [a] -> [a]
omitEmptyList Key
"severity" [Severity]
affectedSeverity
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Pair] -> (dbSpecific -> [Pair]) -> Maybe dbSpecific -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Pair -> [Pair]) -> (dbSpecific -> Pair) -> dbSpecific -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key
"ecosystem_specific" Key -> dbSpecific -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=)) Maybe dbSpecific
affectedEcosystemSpecific
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Pair]
-> (ecosystemSpecific -> [Pair])
-> Maybe ecosystemSpecific
-> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Pair -> [Pair])
-> (ecosystemSpecific -> Pair) -> ecosystemSpecific -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key
"database_specific" Key -> ecosystemSpecific -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=)) Maybe ecosystemSpecific
affectedDatabaseSpecific
where
omitEmptyList :: Key -> [a] -> [a]
omitEmptyList Key
_ [] = []
omitEmptyList Key
k [a]
xs = [Key
k Key -> [a] -> a
forall v. ToJSON v => Key -> v -> a
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [a]
xs]
instance
( ToJSON dbSpecific
, ToJSON affectedEcosystemSpecific
, ToJSON affectedDbSpecific
, ToJSON rangeDbSpecific
) => ToJSON (Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific)
where
toJSON :: Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Value
toJSON Model{[Text]
[Credit]
[Reference]
[Severity]
[Affected
affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
Maybe dbSpecific
Maybe Text
Maybe UTCTime
Text
UTCTime
$sel:modelSchemaVersion:Model :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Text
$sel:modelId:Model :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Text
$sel:modelModified:Model :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> UTCTime
$sel:modelPublished:Model :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Maybe UTCTime
$sel:modelWithdrawn:Model :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Maybe UTCTime
$sel:modelAliases:Model :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> [Text]
$sel:modelRelated:Model :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> [Text]
$sel:modelSummary:Model :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Maybe Text
$sel:modelDetails:Model :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Maybe Text
$sel:modelSeverity:Model :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> [Severity]
$sel:modelAffected:Model :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> [Affected
affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
$sel:modelReferences:Model :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> [Reference]
$sel:modelCredits:Model :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> [Credit]
$sel:modelDatabaseSpecific:Model :: forall dbSpecific affectedEcosystemSpecific affectedDbSpecific
rangeDbSpecific.
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Maybe dbSpecific
modelSchemaVersion :: Text
modelId :: Text
modelModified :: UTCTime
modelPublished :: Maybe UTCTime
modelWithdrawn :: Maybe UTCTime
modelAliases :: [Text]
modelRelated :: [Text]
modelSummary :: Maybe Text
modelDetails :: Maybe Text
modelSeverity :: [Severity]
modelAffected :: [Affected
affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
modelReferences :: [Reference]
modelCredits :: [Credit]
modelDatabaseSpecific :: Maybe dbSpecific
..} = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"schema_version" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
modelSchemaVersion
, Key
"id" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
modelId
, Key
"modified" Key -> UTCTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UTCTime
modelModified
]
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes
[ (Key
"published" Key -> UTCTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=) (UTCTime -> Pair) -> Maybe UTCTime -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe UTCTime
modelPublished
, (Key
"withdrawn" Key -> UTCTime -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=) (UTCTime -> Pair) -> Maybe UTCTime -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe UTCTime
modelWithdrawn
, (Key
"aliases" Key -> [Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=) ([Text] -> Pair) -> Maybe [Text] -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Text] -> Maybe [Text]
forall {a}. [a] -> Maybe [a]
omitEmptyList [Text]
modelAliases
, (Key
"related" Key -> [Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=) ([Text] -> Pair) -> Maybe [Text] -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Text] -> Maybe [Text]
forall {a}. [a] -> Maybe [a]
omitEmptyList [Text]
modelRelated
, (Key
"summary" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=) (Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
modelSummary
, (Key
"details" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=) (Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
modelDetails
, (Key
"severity" Key -> [Severity] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=) ([Severity] -> Pair) -> Maybe [Severity] -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Severity] -> Maybe [Severity]
forall {a}. [a] -> Maybe [a]
omitEmptyList [Severity]
modelSeverity
, (Key
"affected" Key
-> [Affected
affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
-> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=) ([Affected
affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
-> Pair)
-> Maybe
[Affected
affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
-> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Affected
affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
-> Maybe
[Affected
affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
forall {a}. [a] -> Maybe [a]
omitEmptyList [Affected
affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
modelAffected
, (Key
"references" Key -> [Reference] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=) ([Reference] -> Pair) -> Maybe [Reference] -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Reference] -> Maybe [Reference]
forall {a}. [a] -> Maybe [a]
omitEmptyList [Reference]
modelReferences
, (Key
"credits" Key -> [Credit] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=) ([Credit] -> Pair) -> Maybe [Credit] -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Credit] -> Maybe [Credit]
forall {a}. [a] -> Maybe [a]
omitEmptyList [Credit]
modelCredits
, (Key
"database_specific" Key -> dbSpecific -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=) (dbSpecific -> Pair) -> Maybe dbSpecific -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe dbSpecific
modelDatabaseSpecific
]
where
omitEmptyList :: [a] -> Maybe [a]
omitEmptyList [] = Maybe [a]
forall a. Maybe a
Nothing
omitEmptyList [a]
xs = [a] -> Maybe [a]
forall a. a -> Maybe a
Just [a]
xs
instance ToJSON Package where
toJSON :: Package -> Value
toJSON Package{Maybe Text
Text
$sel:packageName:Package :: Package -> Text
$sel:packageEcosystem:Package :: Package -> Text
$sel:packagePurl:Package :: Package -> Maybe Text
packageName :: Text
packageEcosystem :: Text
packagePurl :: Maybe Text
..} = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"name" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
packageName
, Key
"ecosystem" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
packageEcosystem
]
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key
"purl" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.=)) Maybe Text
packagePurl
instance ToJSON Reference where
toJSON :: Reference -> Value
toJSON Reference{Text
ReferenceType
$sel:referencesType:Reference :: Reference -> ReferenceType
$sel:referencesUrl:Reference :: Reference -> Text
referencesType :: ReferenceType
referencesUrl :: Text
..} = [Pair] -> Value
object
[ Key
"type" Key -> ReferenceType -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ReferenceType
referencesType
, Key
"url" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
referencesUrl
]
instance
(FromJSON ecosystemSpecific, FromJSON dbSpecific, FromJSON rangeDbSpecific)
=> FromJSON (Affected ecosystemSpecific dbSpecific rangeDbSpecific) where
parseJSON :: Value
-> Parser (Affected ecosystemSpecific dbSpecific rangeDbSpecific)
parseJSON (Object Object
v) = do
[Range rangeDbSpecific]
affectedRanges <- Object
v Object -> Key -> Parser [Range rangeDbSpecific]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"ranges"
Package
affectedPackage <- Object
v Object -> Key -> Parser Package
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"package"
[Severity]
affectedSeverity <- Object
v Object -> Key -> Parser [Severity]
forall a. FromJSON a => Object -> Key -> Parser [a]
.::? Key
"severity"
Maybe dbSpecific
affectedEcosystemSpecific <- Object
v Object -> Key -> Parser (Maybe dbSpecific)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"ecosystem_specific"
Maybe ecosystemSpecific
affectedDatabaseSpecific <- Object
v Object -> Key -> Parser (Maybe ecosystemSpecific)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"database_specific"
Affected ecosystemSpecific dbSpecific rangeDbSpecific
-> Parser (Affected ecosystemSpecific dbSpecific rangeDbSpecific)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Affected ecosystemSpecific dbSpecific rangeDbSpecific
-> Parser (Affected ecosystemSpecific dbSpecific rangeDbSpecific))
-> Affected ecosystemSpecific dbSpecific rangeDbSpecific
-> Parser (Affected ecosystemSpecific dbSpecific rangeDbSpecific)
forall a b. (a -> b) -> a -> b
$ Affected{[Range rangeDbSpecific]
[Severity]
Maybe ecosystemSpecific
Maybe dbSpecific
Package
$sel:affectedRanges:Affected :: [Range rangeDbSpecific]
$sel:affectedPackage:Affected :: Package
$sel:affectedSeverity:Affected :: [Severity]
$sel:affectedEcosystemSpecific:Affected :: Maybe dbSpecific
$sel:affectedDatabaseSpecific:Affected :: Maybe ecosystemSpecific
affectedRanges :: [Range rangeDbSpecific]
affectedPackage :: Package
affectedSeverity :: [Severity]
affectedEcosystemSpecific :: Maybe dbSpecific
affectedDatabaseSpecific :: Maybe ecosystemSpecific
..}
parseJSON Value
invalid = do
String
-> Parser (Affected ecosystemSpecific dbSpecific rangeDbSpecific)
-> Parser (Affected ecosystemSpecific dbSpecific rangeDbSpecific)
forall a. String -> Parser a -> Parser a
prependFailure String
"parsing Affected failed, "
(String
-> Value
-> Parser (Affected ecosystemSpecific dbSpecific rangeDbSpecific)
forall a. String -> Value -> Parser a
typeMismatch String
"Object" Value
invalid)
parseUTCTime :: Value -> Parser UTCTime
parseUTCTime :: Value -> Parser UTCTime
parseUTCTime = String -> (Text -> Parser UTCTime) -> Value -> Parser UTCTime
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"UTCTime" ((Text -> Parser UTCTime) -> Value -> Parser UTCTime)
-> (Text -> Parser UTCTime) -> Value -> Parser UTCTime
forall a b. (a -> b) -> a -> b
$ \Text
s ->
case String -> Maybe UTCTime
forall (m :: * -> *) t. (MonadFail m, ISO8601 t) => String -> m t
iso8601ParseM (Text -> String
T.unpack Text
s) of
Maybe UTCTime
Nothing -> String -> Value -> Parser UTCTime
forall a. String -> Value -> Parser a
typeMismatch String
"UTCTime" (Text -> Value
String Text
s)
Just UTCTime
t -> UTCTime -> Parser UTCTime
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure UTCTime
t
(.::?) :: FromJSON a => Object -> Key -> Parser [a]
Object
o .::? :: forall a. FromJSON a => Object -> Key -> Parser [a]
.::? Key
k = [a] -> Maybe [a] -> [a]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [a] -> [a]) -> Parser (Maybe [a]) -> Parser [a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe [a])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
k
instance
( FromJSON dbSpecific
, FromJSON affectedEcosystemSpecific
, FromJSON affectedDbSpecific
, FromJSON rangeDbSpecific
) => FromJSON (Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific) where
parseJSON :: Value
-> Parser
(Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific)
parseJSON = String
-> (Object
-> Parser
(Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific))
-> Value
-> Parser
(Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"osv-schema" ((Object
-> Parser
(Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific))
-> Value
-> Parser
(Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific))
-> (Object
-> Parser
(Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific))
-> Value
-> Parser
(Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific)
forall a b. (a -> b) -> a -> b
$ \Object
v -> do
Text
modelSchemaVersion <- Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"schema_version"
Text
modelId <- Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
UTCTime
modelModified <- (Value -> Parser UTCTime) -> Object -> Key -> Parser UTCTime
forall a. (Value -> Parser a) -> Object -> Key -> Parser a
explicitParseField Value -> Parser UTCTime
parseUTCTime Object
v Key
"modified"
Maybe UTCTime
modelPublished <- (Value -> Parser UTCTime)
-> Object -> Key -> Parser (Maybe UTCTime)
forall a. (Value -> Parser a) -> Object -> Key -> Parser (Maybe a)
explicitParseFieldMaybe Value -> Parser UTCTime
parseUTCTime Object
v Key
"published"
Maybe UTCTime
modelWithdrawn <- (Value -> Parser UTCTime)
-> Object -> Key -> Parser (Maybe UTCTime)
forall a. (Value -> Parser a) -> Object -> Key -> Parser (Maybe a)
explicitParseFieldMaybe Value -> Parser UTCTime
parseUTCTime Object
v Key
"withdrawn"
[Text]
modelAliases <- Object
v Object -> Key -> Parser [Text]
forall a. FromJSON a => Object -> Key -> Parser [a]
.::? Key
"aliases"
[Text]
modelRelated <- Object
v Object -> Key -> Parser [Text]
forall a. FromJSON a => Object -> Key -> Parser [a]
.::? Key
"related"
Maybe Text
modelSummary <- Object
v Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"summary"
Maybe Text
modelDetails <- Object
v Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"details"
[Severity]
modelSeverity <- Object
v Object -> Key -> Parser [Severity]
forall a. FromJSON a => Object -> Key -> Parser [a]
.::? Key
"severity"
[Affected
affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
modelAffected <- Object
v Object
-> Key
-> Parser
[Affected
affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
forall a. FromJSON a => Object -> Key -> Parser [a]
.::? Key
"affected"
[Reference]
modelReferences <- Object
v Object -> Key -> Parser [Reference]
forall a. FromJSON a => Object -> Key -> Parser [a]
.::? Key
"references"
[Credit]
modelCredits <- Object
v Object -> Key -> Parser [Credit]
forall a. FromJSON a => Object -> Key -> Parser [a]
.::? Key
"credits"
Maybe dbSpecific
modelDatabaseSpecific <- Object
v Object -> Key -> Parser (Maybe dbSpecific)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"database_specific"
Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Parser
(Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Parser
(Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific))
-> Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific
-> Parser
(Model
dbSpecific
affectedEcosystemSpecific
affectedDbSpecific
rangeDbSpecific)
forall a b. (a -> b) -> a -> b
$ Model{[Text]
[Credit]
[Reference]
[Severity]
[Affected
affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
Maybe dbSpecific
Maybe Text
Maybe UTCTime
Text
UTCTime
$sel:modelSchemaVersion:Model :: Text
$sel:modelId:Model :: Text
$sel:modelModified:Model :: UTCTime
$sel:modelPublished:Model :: Maybe UTCTime
$sel:modelWithdrawn:Model :: Maybe UTCTime
$sel:modelAliases:Model :: [Text]
$sel:modelRelated:Model :: [Text]
$sel:modelSummary:Model :: Maybe Text
$sel:modelDetails:Model :: Maybe Text
$sel:modelSeverity:Model :: [Severity]
$sel:modelAffected:Model :: [Affected
affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
$sel:modelReferences:Model :: [Reference]
$sel:modelCredits:Model :: [Credit]
$sel:modelDatabaseSpecific:Model :: Maybe dbSpecific
modelSchemaVersion :: Text
modelId :: Text
modelModified :: UTCTime
modelPublished :: Maybe UTCTime
modelWithdrawn :: Maybe UTCTime
modelAliases :: [Text]
modelRelated :: [Text]
modelSummary :: Maybe Text
modelDetails :: Maybe Text
modelSeverity :: [Severity]
modelAffected :: [Affected
affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific]
modelReferences :: [Reference]
modelCredits :: [Credit]
modelDatabaseSpecific :: Maybe dbSpecific
..}
instance FromJSON Package where
parseJSON :: Value -> Parser Package
parseJSON (Object Object
v) = do
Text
packageName <- Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Text
packageEcosystem <- Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"ecosystem"
Maybe Text
packagePurl <- Object
v Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"purl"
Package -> Parser Package
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Package -> Parser Package) -> Package -> Parser Package
forall a b. (a -> b) -> a -> b
$ Package{Maybe Text
Text
$sel:packageName:Package :: Text
$sel:packageEcosystem:Package :: Text
$sel:packagePurl:Package :: Maybe Text
packageName :: Text
packageEcosystem :: Text
packagePurl :: Maybe Text
..}
parseJSON Value
invalid = do
String -> Parser Package -> Parser Package
forall a. String -> Parser a -> Parser a
prependFailure String
"parsing Package failed, "
(String -> Value -> Parser Package
forall a. String -> Value -> Parser a
typeMismatch String
"Object" Value
invalid)
instance FromJSON Reference where
parseJSON :: Value -> Parser Reference
parseJSON (Object Object
v) = do
ReferenceType
referencesType <- Object
v Object -> Key -> Parser ReferenceType
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Text
referencesUrl <- Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
Reference -> Parser Reference
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Reference -> Parser Reference) -> Reference -> Parser Reference
forall a b. (a -> b) -> a -> b
$ Reference{Text
ReferenceType
$sel:referencesType:Reference :: ReferenceType
$sel:referencesUrl:Reference :: Text
referencesType :: ReferenceType
referencesUrl :: Text
..}
parseJSON Value
invalid = do
String -> Parser Reference -> Parser Reference
forall a. String -> Parser a -> Parser a
prependFailure String
"parsing References failed, "
(String -> Value -> Parser Reference
forall a. String -> Value -> Parser a
typeMismatch String
"Object" Value
invalid)