crux-0.7: Simple top-level library for Crucible Simulation
Safe HaskellSafe-Inferred
LanguageHaskell2010

Crux.SVCOMP

Description

This module provides various helper functionality for participating in the SV-COMP comptetion, including parsing comptetion set files, configuration data, reporting results, etc.

Synopsis

Documentation

data SVCOMPOptions (f :: Type -> Type) Source #

Constructors

SVCOMPOptions 

Fields

data Arch Source #

Constructors

Arch32 
Arch64 

Instances

Instances details
Show Arch Source # 
Instance details

Defined in Crux.SVCOMP

Methods

showsPrec :: Int -> Arch -> ShowS #

show :: Arch -> String #

showList :: [Arch] -> ShowS #

Eq Arch Source # 
Instance details

Defined in Crux.SVCOMP

Methods

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

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

Ord Arch Source # 
Instance details

Defined in Crux.SVCOMP

Methods

compare :: Arch -> Arch -> Ordering #

(<) :: Arch -> Arch -> Bool #

(<=) :: Arch -> Arch -> Bool #

(>) :: Arch -> Arch -> Bool #

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

max :: Arch -> Arch -> Arch #

min :: Arch -> Arch -> Arch #

parseArch :: (Arch -> opts -> opts) -> String -> OptSetter opts Source #

processSVCOMPOptions :: SVCOMPOptions Maybe -> IO (SVCOMPOptions Identity) Source #

We cannot verify an SV-COMP program without knowing the architecture and the specification. Unfortunately, Crux's command-line argument parser makes it somewhat awkward to require certain arguments (without defaults). As a hacky workaround, we parse the command-line arguments for the architecture/specification as if they were optional and later check here to see if they were actually provided, throwing an error if they were not provided.

data ComputedVerdict Source #

Constructors

Verified 
Falsified 
Unknown 

Instances

Instances details
ToJSON ComputedVerdict Source # 
Instance details

Defined in Crux.SVCOMP

Generic ComputedVerdict Source # 
Instance details

Defined in Crux.SVCOMP

Associated Types

type Rep ComputedVerdict :: Type -> Type #

Show ComputedVerdict Source # 
Instance details

Defined in Crux.SVCOMP

Eq ComputedVerdict Source # 
Instance details

Defined in Crux.SVCOMP

Ord ComputedVerdict Source # 
Instance details

Defined in Crux.SVCOMP

type Rep ComputedVerdict Source # 
Instance details

Defined in Crux.SVCOMP

type Rep ComputedVerdict = D1 ('MetaData "ComputedVerdict" "Crux.SVCOMP" "crux-0.7-DD4jascIe8aJ5p2f7vnjLq" 'False) (C1 ('MetaCons "Verified" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Falsified" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unknown" 'PrefixI 'False) (U1 :: Type -> Type)))

data SVCompProperty Source #

Instances

Instances details
ToJSON SVCompProperty Source # 
Instance details

Defined in Crux.SVCOMP

Generic SVCompProperty Source # 
Instance details

Defined in Crux.SVCOMP

Associated Types

type Rep SVCompProperty :: Type -> Type #

Show SVCompProperty Source # 
Instance details

Defined in Crux.SVCOMP

Eq SVCompProperty Source # 
Instance details

Defined in Crux.SVCOMP

Ord SVCompProperty Source # 
Instance details

Defined in Crux.SVCOMP

type Rep SVCompProperty Source # 
Instance details

Defined in Crux.SVCOMP

type Rep SVCompProperty = D1 ('MetaData "SVCompProperty" "Crux.SVCOMP" "crux-0.7-DD4jascIe8aJ5p2f7vnjLq" 'False) (((C1 ('MetaCons "CheckNoError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "CheckValidFree" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CheckValidDeref" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CheckValidMemtrack" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CheckValidMemCleanup" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CheckDefBehavior" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CheckNoOverflow" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CheckTerminates" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CoverageFQL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))))

data CDataModel Source #

Constructors

ILP32 
LP64 

Instances

Instances details
Show CDataModel Source # 
Instance details

Defined in Crux.SVCOMP

Eq CDataModel Source # 
Instance details

Defined in Crux.SVCOMP

Ord CDataModel Source # 
Instance details

Defined in Crux.SVCOMP

deduplicateTasks :: [BenchmarkSet] -> TaskMap Source #

There is significant overlap between the various verification tasks found in different benchmark sets in the SV-COMP repository. This operation collects together all the potentially duplicated tasks found in a collection of benchmark sets and places them in a map, ensuring there is at most one reference to each one. The tasks are the keys of the map; the benchmark set(s) that referenced a given task are stored in the elements the map.