osv-0.1.0.0: Open Source Vulnerability format
Safe HaskellSafe-Inferred
LanguageHaskell2010

Security.OSV

Description

This module contains the OSV datatype and its ToJSON instance. The module was initialized with http://json-to-haskell.chrispenner.ca/

Synopsis

Top-level data type

data Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific Source #

OSV model parameterised over database-specific and ecosystem-specific fields.

A naïve consumer can parse Model Value Value Value Value for no loss of information.

A producer can instantiate unused database/ecosystem-specific fields at Data.Void.Void. () is not recommended, because Just () will serialise as an empty JSON array.

Constructors

Model 

Fields

Instances

Instances details
(FromJSON dbSpecific, FromJSON affectedEcosystemSpecific, FromJSON affectedDbSpecific, FromJSON rangeDbSpecific) => FromJSON (Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific) Source # 
Instance details

Defined in Security.OSV

Methods

parseJSON :: Value -> Parser (Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific) #

parseJSONList :: Value -> Parser [Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific] #

omittedField :: Maybe (Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific) #

(ToJSON dbSpecific, ToJSON affectedEcosystemSpecific, ToJSON affectedDbSpecific, ToJSON rangeDbSpecific) => ToJSON (Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific) Source # 
Instance details

Defined in Security.OSV

Methods

toJSON :: Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific -> Value #

toEncoding :: Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific -> Encoding #

toJSONList :: [Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific] -> Value #

toEncodingList :: [Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific] -> Encoding #

omitField :: Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific -> Bool #

(Show rangeDbSpecific, Show affectedDbSpecific, Show affectedEcosystemSpecific, Show dbSpecific) => Show (Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific) Source # 
Instance details

Defined in Security.OSV

Methods

showsPrec :: Int -> Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific -> ShowS #

show :: Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific -> String #

showList :: [Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific] -> ShowS #

(Eq rangeDbSpecific, Eq affectedDbSpecific, Eq affectedEcosystemSpecific, Eq dbSpecific) => Eq (Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific) Source # 
Instance details

Defined in Security.OSV

Methods

(==) :: Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific -> Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific -> Bool #

(/=) :: Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific -> Model dbSpecific affectedEcosystemSpecific affectedDbSpecific rangeDbSpecific -> Bool #

newModel Source #

Arguments

:: Text

schema version

-> Text

id

-> UTCTime

modified

-> Model dbs aes adbs rdbs 

Construct a new model with only the required fields

newModel' Source #

Arguments

:: Text

id

-> UTCTime

modified

-> Model dbs aes adbs rdbs 

Construct a new model given id and modified values, using defaultSchemaVersion.

defaultSchemaVersion :: Text Source #

Schema version implemented by this library. Currently 1.5.0.

Subsidiary data types

data Affected dbSpecific ecosystemSpecific rangeDbSpecific Source #

Constructors

Affected 

Fields

Instances

Instances details
(FromJSON ecosystemSpecific, FromJSON dbSpecific, FromJSON rangeDbSpecific) => FromJSON (Affected ecosystemSpecific dbSpecific rangeDbSpecific) Source # 
Instance details

Defined in Security.OSV

Methods

parseJSON :: Value -> Parser (Affected ecosystemSpecific dbSpecific rangeDbSpecific) #

parseJSONList :: Value -> Parser [Affected ecosystemSpecific dbSpecific rangeDbSpecific] #

omittedField :: Maybe (Affected ecosystemSpecific dbSpecific rangeDbSpecific) #

(ToJSON ecosystemSpecific, ToJSON dbSpecific, ToJSON rangeDbSpecific) => ToJSON (Affected ecosystemSpecific dbSpecific rangeDbSpecific) Source # 
Instance details

Defined in Security.OSV

Methods

toJSON :: Affected ecosystemSpecific dbSpecific rangeDbSpecific -> Value #

toEncoding :: Affected ecosystemSpecific dbSpecific rangeDbSpecific -> Encoding #

toJSONList :: [Affected ecosystemSpecific dbSpecific rangeDbSpecific] -> Value #

toEncodingList :: [Affected ecosystemSpecific dbSpecific rangeDbSpecific] -> Encoding #

omitField :: Affected ecosystemSpecific dbSpecific rangeDbSpecific -> Bool #

(Show rangeDbSpecific, Show ecosystemSpecific, Show dbSpecific) => Show (Affected dbSpecific ecosystemSpecific rangeDbSpecific) Source # 
Instance details

Defined in Security.OSV

Methods

showsPrec :: Int -> Affected dbSpecific ecosystemSpecific rangeDbSpecific -> ShowS #

show :: Affected dbSpecific ecosystemSpecific rangeDbSpecific -> String #

showList :: [Affected dbSpecific ecosystemSpecific rangeDbSpecific] -> ShowS #

(Eq rangeDbSpecific, Eq ecosystemSpecific, Eq dbSpecific) => Eq (Affected dbSpecific ecosystemSpecific rangeDbSpecific) Source # 
Instance details

Defined in Security.OSV

Methods

(==) :: Affected dbSpecific ecosystemSpecific rangeDbSpecific -> Affected dbSpecific ecosystemSpecific rangeDbSpecific -> Bool #

(/=) :: Affected dbSpecific ecosystemSpecific rangeDbSpecific -> Affected dbSpecific ecosystemSpecific rangeDbSpecific -> Bool #

data Credit Source #

Constructors

Credit 

Fields

  • creditType :: CreditType
     
  • creditName :: Text

    The name, label, or other identifier of the individual or entity being credited, using whatever notation the creditor prefers.

  • creditContacts :: [Text]

    Fully qualified, plain-text URLs at which the credited can be reached.

Instances

Instances details
FromJSON Credit Source # 
Instance details

Defined in Security.OSV

ToJSON Credit Source # 
Instance details

Defined in Security.OSV

Show Credit Source # 
Instance details

Defined in Security.OSV

Eq Credit Source # 
Instance details

Defined in Security.OSV

Methods

(==) :: Credit -> Credit -> Bool #

(/=) :: Credit -> Credit -> Bool #

data CreditType Source #

Types of individuals or entities to be credited in relation to an advisory.

Constructors

CreditTypeFinder

Identified the vulnerability

CreditTypeReporter

Notified the vendor of the vulnerability to a CNA

CreditTypeAnalyst

Validated the vulnerability to ensure accuracy or severity

CreditTypeCoordinator

Facilitated the coordinated response process

CreditTypeRemediationDeveloper

prepared a code change or other remediation plans

CreditTypeRemediationReviewer

Reviewed vulnerability remediation plans or code changes for effectiveness and completeness

CreditTypeRemediationVerifier

Tested and verified the vulnerability or its remediation

CreditTypeTool

Names of tools used in vulnerability discovery or identification

CreditTypeSponsor

Supported the vulnerability identification or remediation activities

CreditTypeOther

Any other type or role that does not fall under the categories described above

creditTypes :: [(CreditType, Text)] Source #

Bijection of credit types and their string representations

data Event a Source #

Instances

Instances details
FromJSON a => FromJSON (Event a) Source # 
Instance details

Defined in Security.OSV

ToJSON a => ToJSON (Event a) Source # 
Instance details

Defined in Security.OSV

Show a => Show (Event a) Source # 
Instance details

Defined in Security.OSV

Methods

showsPrec :: Int -> Event a -> ShowS #

show :: Event a -> String #

showList :: [Event a] -> ShowS #

Eq a => Eq (Event a) Source # 
Instance details

Defined in Security.OSV

Methods

(==) :: Event a -> Event a -> Bool #

(/=) :: Event a -> Event a -> Bool #

Ord a => Ord (Event a) Source # 
Instance details

Defined in Security.OSV

Methods

compare :: 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 #

max :: Event a -> Event a -> Event a #

min :: Event a -> Event a -> Event a #

data Package Source #

Instances

Instances details
FromJSON Package Source # 
Instance details

Defined in Security.OSV

ToJSON Package Source # 
Instance details

Defined in Security.OSV

Show Package Source # 
Instance details

Defined in Security.OSV

Eq Package Source # 
Instance details

Defined in Security.OSV

Methods

(==) :: Package -> Package -> Bool #

(/=) :: Package -> Package -> Bool #

Ord Package Source # 
Instance details

Defined in Security.OSV

data Range dbSpecific Source #

Constructors

RangeSemVer [Event Text] (Maybe dbSpecific) 
RangeEcosystem [Event Text] (Maybe dbSpecific) 
RangeGit 

Fields

Instances

Instances details
FromJSON dbSpecific => FromJSON (Range dbSpecific) Source # 
Instance details

Defined in Security.OSV

Methods

parseJSON :: Value -> Parser (Range dbSpecific) #

parseJSONList :: Value -> Parser [Range dbSpecific] #

omittedField :: Maybe (Range dbSpecific) #

ToJSON dbSpecific => ToJSON (Range dbSpecific) Source # 
Instance details

Defined in Security.OSV

Methods

toJSON :: Range dbSpecific -> Value #

toEncoding :: Range dbSpecific -> Encoding #

toJSONList :: [Range dbSpecific] -> Value #

toEncodingList :: [Range dbSpecific] -> Encoding #

omitField :: Range dbSpecific -> Bool #

Show dbSpecific => Show (Range dbSpecific) Source # 
Instance details

Defined in Security.OSV

Methods

showsPrec :: Int -> Range dbSpecific -> ShowS #

show :: Range dbSpecific -> String #

showList :: [Range dbSpecific] -> ShowS #

Eq dbSpecific => Eq (Range dbSpecific) Source # 
Instance details

Defined in Security.OSV

Methods

(==) :: Range dbSpecific -> Range dbSpecific -> Bool #

(/=) :: Range dbSpecific -> Range dbSpecific -> Bool #

data Reference Source #

Instances

Instances details
FromJSON Reference Source # 
Instance details

Defined in Security.OSV

ToJSON Reference Source # 
Instance details

Defined in Security.OSV

Show Reference Source # 
Instance details

Defined in Security.OSV

Eq Reference Source # 
Instance details

Defined in Security.OSV

data ReferenceType Source #

Constructors

ReferenceTypeAdvisory

A published security advisory for the vulnerability.

ReferenceTypeArticle

An article or blog post describing the vulnerability.

ReferenceTypeDetection

A tool, script, scanner, or other mechanism that allows for detection of the vulnerability in production environments. e.g. YARA rules, hashes, virus signature, or other scanners.

ReferenceTypeDiscussion

A social media discussion regarding the vulnerability, e.g. a Twitter, Mastodon, Hacker News, or Reddit thread.

ReferenceTypeReport

A report, typically on a bug or issue tracker, of the vulnerability.

ReferenceTypeFix

A source code browser link to the fix (e.g., a GitHub commit) Note that the Fix type is meant for viewing by people using web browsers. Programs interested in analyzing the exact commit range would do better to use the GIT-typed affected Range entries.

ReferenceTypeIntroduced

A source code browser link to the introduction of the vulnerability (e.g., a GitHub commit) Note that the introduced type is meant for viewing by people using web browsers. Programs interested in analyzing the exact commit range would do better to use the GIT-typed affected Range entries.

ReferenceTypePackage

A home web page for the package.

ReferenceTypeEvidence

A demonstration of the validity of a vulnerability claim, e.g. app.any.run replaying the exploitation of the vulnerability.

ReferenceTypeWeb

A web page of some unspecified kind.

referenceTypes :: [(ReferenceType, Text)] Source #

Bijection of reference types and their string representations

newtype Severity Source #

Severity. There is no Ord instance. Severity scores should be calculated and compared in a more nuanced way than Ord can provide for.

Constructors

Severity CVSS 

Instances

Instances details
FromJSON Severity Source # 
Instance details

Defined in Security.OSV

ToJSON Severity Source # 
Instance details

Defined in Security.OSV

Show Severity Source # 
Instance details

Defined in Security.OSV

Eq Severity Source # 
Instance details

Defined in Security.OSV