Copyright | (c) Galois Inc 2015-2016 |
---|---|
License | BSD3 |
Maintainer | rdockins@galois.com |
Stability | provisional |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Lang.Crucible.LLVM
Description
Synopsis
- data LLVM
- registerModule :: (1 <= ArchWidth arch, HasPtrWidth (ArchWidth arch), IsSymInterface sym) => (LLVMTranslationWarning -> IO ()) -> ModuleTranslation arch -> OverrideSim p sym LLVM rtp l a ()
- registerModuleFn :: (1 <= ArchWidth arch, HasPtrWidth (ArchWidth arch), IsSymInterface sym) => (LLVMTranslationWarning -> IO ()) -> ModuleTranslation arch -> Symbol -> OverrideSim p sym LLVM rtp l a ()
- registerLazyModule :: (1 <= ArchWidth arch, HasPtrWidth (ArchWidth arch), IsSymInterface sym) => (LLVMTranslationWarning -> IO ()) -> ModuleTranslation arch -> OverrideSim p sym LLVM rtp l a ()
- registerLazyModuleFn :: (1 <= ArchWidth arch, HasPtrWidth (ArchWidth arch), IsSymInterface sym) => (LLVMTranslationWarning -> IO ()) -> ModuleTranslation arch -> Symbol -> OverrideSim p sym LLVM rtp l a ()
- llvmGlobalsToCtx :: LLVMContext arch -> MemImpl sym -> SymGlobalState sym
- llvmGlobals :: GlobalVar Mem -> MemImpl sym -> SymGlobalState sym
- register_llvm_overrides :: (IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr, wptr ~ ArchWidth arch, ?intrinsicsOpts :: IntrinsicsOptions, ?memOpts :: MemOptions) => Module -> [OverrideTemplate p sym LLVM arch] -> [OverrideTemplate p sym LLVM arch] -> LLVMContext arch -> OverrideSim p sym LLVM rtp l a ([SomeLLVMOverride p sym LLVM], [SomeLLVMOverride p sym LLVM])
- llvmExtensionImpl :: HasLLVMAnn sym => MemOptions -> ExtensionImpl p sym LLVM
Documentation
The Crucible extension type marker for LLVM.
Instances
Data LLVM Source # | |
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 # 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 # | |
IsSyntaxExtension LLVM Source # | |
Defined in Lang.Crucible.LLVM.Extension | |
Eq LLVM Source # | |
Ord LLVM Source # | |
type Rep LLVM Source # | |
type ExprExtension LLVM Source # | |
Defined in Lang.Crucible.LLVM.Extension | |
type StmtExtension LLVM Source # | |
Defined in Lang.Crucible.LLVM.Extension |
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.
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.
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.
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.
llvmGlobalsToCtx :: LLVMContext arch -> MemImpl sym -> SymGlobalState sym Source #
llvmGlobals :: GlobalVar Mem -> MemImpl sym -> SymGlobalState sym Source #
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 ( |
Match two sets of OverrideTemplate
s against the declare
s and define
s
in a Module
, registering all the overrides that apply and returning them
as a list.
llvmExtensionImpl :: HasLLVMAnn sym => MemOptions -> ExtensionImpl p sym LLVM Source #