crucible-llvm-0.6: Support for translating and executing LLVM code in Crucible
Copyright(c) Galois Inc 2015-2016
LicenseBSD3
Maintainerrdockins@galois.com
Stabilityprovisional
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lang.Crucible.LLVM

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.6-JJ7tfvbGrbFFTkl5eJBN3H" '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

registerModule Source #

Arguments

:: (1 <= ArchWidth arch, HasPtrWidth (ArchWidth arch), IsSymInterface sym) 
=> (LLVMTranslationWarning -> IO ())

A callback for handling traslation warnings

-> ModuleTranslation arch 
-> OverrideSim p sym LLVM rtp l a () 

Register all the functions defined in the LLVM module. This will immediately build Crucible CFGs for each function defined in the module.

registerModuleFn Source #

Arguments

:: (1 <= ArchWidth arch, HasPtrWidth (ArchWidth arch), IsSymInterface sym) 
=> (LLVMTranslationWarning -> IO ())

A callback for handling traslation warnings

-> ModuleTranslation arch 
-> Symbol 
-> OverrideSim p sym LLVM rtp l a () 

Register a specific named function that is defined in the given module translation. This will immediately build a Crucible CFG for the named function.

registerLazyModule Source #

Arguments

:: (1 <= ArchWidth arch, HasPtrWidth (ArchWidth arch), IsSymInterface sym) 
=> (LLVMTranslationWarning -> IO ())

A callback for handling traslation warnings

-> ModuleTranslation arch 
-> OverrideSim p sym LLVM rtp l a () 

Lazily register all the functions defined in the LLVM module. See registerLazyModuleFn for a description.

registerLazyModuleFn Source #

Arguments

:: (1 <= ArchWidth arch, HasPtrWidth (ArchWidth arch), IsSymInterface sym) 
=> (LLVMTranslationWarning -> IO ())

A callback for handling translation warnings

-> ModuleTranslation arch 
-> Symbol 
-> OverrideSim p sym LLVM rtp l a () 

Lazily register the named function that is defnied in the given module translation. This will delay actually translating the function until it is called. This done by first installing a bootstrapping override that will peform the actual translation when first invoked, and then will backpatch its own references to point to the translated function.

Note that the callback for printing translation warnings may be called at a much-later point, when the function in question is actually first invoked.

register_llvm_overrides Source #

Arguments

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

Additional "define" overrides

-> [OverrideTemplate p sym arch rtp l a]

Additional "declare" overrides

-> LLVMContext arch 
-> OverrideSim p sym LLVM rtp l a () 

Register all declare and define overrides