crucible-llvm-0.7.1: Support for translating and executing LLVM code in Crucible
Copyright(c) Galois Inc 2015-2016
LicenseBSD3
MaintainerRob Dockins <rdockins@galois.com>
Stabilityprovisional
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lang.Crucible.LLVM.Intrinsics

Description

 
Synopsis

Documentation

data LLVM Source #

The Crucible extension type marker for LLVM.

Instances

Instances details
Data LLVM Source # 
Instance details

Defined in Lang.Crucible.LLVM.Extension

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LLVM -> c LLVM #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LLVM #

toConstr :: LLVM -> Constr #

dataTypeOf :: LLVM -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LLVM) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LLVM) #

gmapT :: (forall b. Data b => b -> b) -> LLVM -> LLVM #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LLVM -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LLVM -> r #

gmapQ :: (forall d. Data d => d -> u) -> LLVM -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LLVM -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LLVM -> m LLVM #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LLVM -> m LLVM #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LLVM -> m LLVM #

Generic LLVM Source # 
Instance details

Defined in Lang.Crucible.LLVM.Extension

Associated Types

type Rep LLVM :: Type -> Type #

Methods

from :: LLVM -> Rep LLVM x #

to :: Rep LLVM x -> LLVM #

IsSyntaxExtension LLVM Source # 
Instance details

Defined in Lang.Crucible.LLVM.Extension

Eq LLVM Source # 
Instance details

Defined in Lang.Crucible.LLVM.Extension

Methods

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

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

Ord LLVM Source # 
Instance details

Defined in Lang.Crucible.LLVM.Extension

Methods

compare :: LLVM -> LLVM -> Ordering #

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

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

(>) :: LLVM -> LLVM -> Bool #

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

max :: LLVM -> LLVM -> LLVM #

min :: LLVM -> LLVM -> LLVM #

type Rep LLVM Source # 
Instance details

Defined in Lang.Crucible.LLVM.Extension

type Rep LLVM = D1 ('MetaData "LLVM" "Lang.Crucible.LLVM.Extension" "crucible-llvm-0.7.1-I6hsKTgEWFKDhgfTwE350s" 'False) (V1 :: Type -> Type)
type ExprExtension LLVM Source # 
Instance details

Defined in Lang.Crucible.LLVM.Extension

type StmtExtension LLVM Source # 
Instance details

Defined in Lang.Crucible.LLVM.Extension

data LLVMOverride p sym ext args ret Source #

This type represents an implementation of an LLVM intrinsic function in Crucible.

This is parameterized over ext so that LLVMOverrides can more easily be reused in the context of other language extensions that are also based on the LLVM memory model, such as Macaw.

Constructors

LLVMOverride 

Fields

register_llvm_overrides Source #

Arguments

:: (IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr, wptr ~ ArchWidth arch, ?intrinsicsOpts :: IntrinsicsOptions, ?memOpts :: MemOptions) 
=> Module 
-> [OverrideTemplate p sym LLVM arch]

Additional "define" overrides

-> [OverrideTemplate p sym LLVM arch]

Additional "declare" overrides

-> LLVMContext arch 
-> OverrideSim p sym LLVM rtp l a ([SomeLLVMOverride p sym LLVM], [SomeLLVMOverride p sym LLVM])

Applied (define overrides, declare overrides)

Match two sets of OverrideTemplates against the declares and defines in a Module, registering all the overrides that apply and returning them as a list.

register_llvm_overrides_ Source #

Arguments

:: (IsSymInterface sym, HasLLVMAnn sym) 
=> LLVMContext arch 
-> [OverrideTemplate p sym ext arch]

Overrides to attempt to match against these declarations

-> [Declare]

Declarations of the functions that might get overridden

-> OverrideSim p sym ext rtp l a [SomeLLVMOverride p sym ext] 

Match a set of OverrideTemplates against a set of Declares, registering all the overrides that apply and returning them as a list.

llvmDeclToFunHandleRepr :: HasPtrWidth wptr => FunDecl -> (forall args ret. CtxRepr args -> TypeRepr ret -> a) -> a Source #

Compute the function Crucible function signature that corresponds to the given LLVM function declaration.

data LLVMOverride p sym ext args ret Source #

This type represents an implementation of an LLVM intrinsic function in Crucible.

This is parameterized over ext so that LLVMOverrides can more easily be reused in the context of other language extensions that are also based on the LLVM memory model, such as Macaw.

Constructors

LLVMOverride 

Fields

data SomeLLVMOverride p sym ext Source #

Constructors

forall args ret. SomeLLVMOverride (LLVMOverride p sym ext args ret) 

newtype MakeOverride p sym ext arch Source #

A funcion that inspects an LLVM declaration (along with some other data), and constructs an override for the declaration if it can.

Constructors

MakeOverride 

llvmSizeT :: HasPtrWidth wptr => Type Source #

Convenient LLVM representation of the size_t type.

llvmSSizeT :: HasPtrWidth wptr => Type Source #

Convenient LLVM representation of the ssize_t type.

data OverrideTemplate p sym ext arch Source #

Checking if an override applies to a given declaration happens in two "phases", corresponding to the fields of this struct.

Constructors

OverrideTemplate 

Fields

register_llvm_override

basic_llvm_override :: forall p args ret sym ext arch wptr. (IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) => LLVMOverride p sym ext args ret -> OverrideTemplate p sym ext arch Source #

polymorphic1_llvm_override :: forall p sym ext arch wptr. (IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) => String -> (forall w. 1 <= w => NatRepr w -> SomeLLVMOverride p sym ext) -> OverrideTemplate p sym ext arch Source #

polymorphic1_vec_llvm_override :: forall p sym ext arch wptr. (IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) => String -> (forall vecSz intSz. 1 <= intSz => NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext) -> OverrideTemplate p sym ext arch Source #

Create an OverrideTemplate for a polymorphic LLVM override involving a vector type. For example, the llvm.vector.reduce.add.* intrinsic can be instantiated at multiple types, including:

  • i32 @llvm.vector.reduce.add.v4i32(x i32)
  • i64 @llvm.vector.reduce.add.v2i64(x i64)
  • etc.

Note that the intrinsic can vary both by the size of the vector type (4, 2, etc.) and the size of the integer type used as the vector element type (i32, i64, etc.) Therefore, the fn argument that this function accepts is parameterized by both the vector size (vecSz) and the integer size (intSz).

build_llvm_override :: HasLLVMAnn sym => FunctionName -> CtxRepr args -> TypeRepr ret -> CtxRepr args' -> TypeRepr ret' -> (forall rtp' l' a'. IsSymInterface sym => Assignment (RegEntry sym) args -> OverrideSim p sym ext rtp' l' a' (RegValue sym ret)) -> OverrideSim p sym ext rtp l a (Override p sym ext args' ret') Source #

Do some pipe-fitting to match a Crucible override function into the shape expected by the LLVM calling convention. This basically just coerces between values of BVType w and values of LLVMPointerType w.

register_llvm_override :: forall p args ret sym ext arch wptr rtp l a. (IsSymInterface sym, HasPtrWidth wptr, HasLLVMAnn sym) => LLVMOverride p sym ext args ret -> Declare -> LLVMContext arch -> OverrideSim p sym ext rtp l a () Source #

register_1arg_polymorphic_override :: forall p sym ext arch wptr. (IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) => String -> (forall w. 1 <= w => NatRepr w -> SomeLLVMOverride p sym ext) -> MakeOverride p sym ext arch Source #

register_1arg_vec_polymorphic_override :: forall p sym ext arch wptr. (IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) => String -> (forall vecSz intSz. 1 <= intSz => NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext) -> MakeOverride p sym ext arch Source #

Register a polymorphic LLVM override involving a vector type. (See the Haddocks for polymorphic1_vec_llvm_override for details on what this means.) This function is responsible for parsing the suffix in the intrinsic's name, which encodes the sizes of the vector and integer types. As some examples:

  • .v4i32 (vector size 4, integer size 32)
  • .v2i64 (vector size 2, integer size 64)

do_register_llvm_override :: forall p args ret sym ext arch wptr l a rtp. (IsSymInterface sym, HasPtrWidth wptr, HasLLVMAnn sym) => LLVMContext arch -> LLVMOverride p sym ext args ret -> OverrideSim p sym ext rtp l a () Source #

Low-level function to register LLVM overrides.

Type-checks the LLVM override against the Declare it contains, adapting its arguments and return values as necessary. Then creates and binds a function handle, and also binds the function to the global function allocation in the LLVM memory.

Useful when you don't have access to a full LLVM AST, e.g., when parsing Crucible CFGs written in crucible-syntax. For more usual cases, use register_llvm_overrides.

alloc_and_register_override Source #

Arguments

:: (IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts :: MemOptions) 
=> bak 
-> LLVMContext arch 
-> LLVMOverride p sym LLVM args ret 
-> [Symbol]

Aliases

-> OverrideSim p sym LLVM rtp l a () 

Create an allocation for an override and register it.

Useful when registering an override for a function in an LLVM memory that wasn't initialized with the functions in Lang.Crucible.LLVM.Globals, e.g., when parsing Crucible CFGs written in crucible-syntax. For more usual cases, use register_llvm_overrides.

c.f. allocLLVMFunPtr

newtype IntrinsicsOptions Source #

This datatype encodes a variety of tweakable settings that to LLVM overrides.

Constructors

IntrinsicsOptions 

Fields

data AbnormalExitBehavior Source #

Should Crucible fail when simulating a function which triggers an abnormal exit, such as abort()?

Constructors

AlwaysFail

Functions which trigger an abnormal exit will always cause Crucible to fail.

OnlyAssertFail

The __assert_fail() or __assert_rtn() functions will cause Crucible to fail, while other functions which trigger an abnormal exit will not cause failures. This option is primarily useful for SV-COMP.

NeverFail

Functions which trigger an abnormal exit will never cause Crucible to fail. This option is primarily useful for SV-COMP.

defaultIntrinsicsOptions :: IntrinsicsOptions Source #

The default translation options:

  • Functions which trigger an abnormal exit will always cause Crucible to fail.

data TemplateMatcher Source #

This type controls whether an override is installed for a given name found in a module. See filterTemplates.

Constructors

ExactMatch String 
PrefixMatch String 
SubstringsMatch [String] 
DarwinAliasMatch String

Match a name up to some number of Darwin aliases. See Note [Darwin aliases].

matches Source #

Arguments

:: String

Function name

-> TemplateMatcher 
-> Bool 

Check whether a TemplateMatcher matches a given function name.

stripDarwinAliases :: String -> String Source #

Remove all prefixes and suffixes that might occur in a Darwin alias for a function name. See Note [Darwin aliases].