| Copyright | (c) Galois Inc 2024 |
|---|---|
| License | BSD3 |
| Maintainer | Langston Barrett <langston@galois.com> |
| Stability | provisional |
| Safe Haskell | None |
| Language | Haskell2010 |
Lang.Crucible.LLVM.Functions
Description
Registering functions to be used with the LLVM memory model is somewhat more complex than for other Crucible frontends, as LLVM has a notion of function pointers. Each function to be registered has to go through a few steps (the first two are common to all Crucible frontends):
- Create a
FnHandleand aFnState(a translated CFG or an override) - Bind the
FnHandleto theFnState(bindFnHandle) - Create a (global, immutable, zero-sized) allocation corresponding to the
function in the
MemImpl(allocFunPtr) - Register the correspondence between the function's name (and any aliases)
and its global allocation (
registerGlobal, or viaregisterFunPtr) - Register the correspondence between the function's allocation and its
handle (
doInstallHandle, or viabindLLVMHandle,bindLLVMCFG, orbindLLVMFunc)
This module provides helpers to accomplish all of this. They're ordered roughly low-levelcustomizable to high-levelautomated.
Perhaps surprisingly, there's no function that does all of the above at once. This is because there are two main places where binding functions happens:
- Lang.Crucible.LLVM registers translated CFGs, but does so lazily. In particular, this means that it initially binds the handle and allocation to a "stub" that, when called, will translate the actual CFG and then re-bind the handle and allocation to it.
- Lang.Crucible.LLVM.Intrinsics.Common registers overrides, which generally
apply to functions that are
declared but notdefined. Thus, they already have corresponding allocations, which just need to be associated with the override.
Prior to these, function allocation happens in
initializeMemory.
Synopsis
- allocFunPtr :: forall sym bak (wptr :: Natural). (IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts :: MemOptions) => bak -> MemImpl sym -> String -> IO (LLVMPtr sym wptr, MemImpl sym)
- allocLLVMFunPtr :: forall sym bak (wptr :: Natural) (arch :: LLVMArch). (IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts :: MemOptions) => bak -> LLVMContext arch -> MemImpl sym -> Either Declare Define -> IO (LLVMPtr sym wptr, MemImpl sym)
- allocLLVMFunPtrs :: forall sym bak (wptr :: Natural) (arch :: LLVMArch). (IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts :: MemOptions) => bak -> LLVMContext arch -> MemImpl sym -> Module -> IO (MemImpl sym)
- registerFunPtr :: forall sym bak (wptr :: Natural). (IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts :: MemOptions) => bak -> MemImpl sym -> String -> Symbol -> [Symbol] -> IO (LLVMPtr sym wptr, MemImpl sym)
- bindLLVMFunPtr :: forall sym bak (wptr :: Natural) (args :: Ctx CrucibleType) (ret :: CrucibleType). (IsSymBackend sym bak, HasPtrWidth wptr) => bak -> Symbol -> FnHandle args ret -> MemImpl sym -> IO (MemImpl sym)
- bindLLVMHandle :: forall sym (wptr :: Natural) (args :: Ctx CrucibleType) (ret :: CrucibleType) p ext rtp (l :: Ctx CrucibleType) (a :: CrucibleType). (IsSymInterface sym, HasPtrWidth wptr) => GlobalVar Mem -> Symbol -> FnHandle args ret -> FnState p sym ext args ret -> OverrideSim p sym ext rtp l a ()
- bindLLVMCFG :: forall sym (wptr :: Natural) (blocks :: Ctx (Ctx CrucibleType)) (init :: Ctx CrucibleType) (ret :: CrucibleType) p rtp (l :: Ctx CrucibleType) (a :: CrucibleType). (IsSymInterface sym, HasPtrWidth wptr) => GlobalVar Mem -> Symbol -> CFG LLVM blocks init ret -> OverrideSim p sym LLVM rtp l a ()
- bindLLVMFunc :: forall sym (wptr :: Natural) (args :: Ctx CrucibleType) (ret :: CrucibleType) p ext rtp (l :: Ctx CrucibleType) (a :: CrucibleType). (IsSymInterface sym, HasPtrWidth wptr) => GlobalVar Mem -> Symbol -> Assignment TypeRepr args -> TypeRepr ret -> FnState p sym ext args ret -> OverrideSim p sym ext rtp l a ()
Documentation
Arguments
| :: forall sym bak (wptr :: Natural). (IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts :: MemOptions) | |
| => bak | |
| -> MemImpl sym | |
| -> String | Function Name |
| -> IO (LLVMPtr sym wptr, MemImpl sym) |
Create a global allocation to be assocated with a function.
The returned allocation is global (GlobalAlloc), immutable
(Immutable), and has a size and alignment of zero.
allocLLVMFunPtr :: forall sym bak (wptr :: Natural) (arch :: LLVMArch). (IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts :: MemOptions) => bak -> LLVMContext arch -> MemImpl sym -> Either Declare Define -> IO (LLVMPtr sym wptr, MemImpl sym) Source #
Create a global allocation assocated with a function (see allocFunPtr),
register the function's primary symbol and its aliases as associated with
that allocation (see registerFunPtr), looking up the aliases from the
LLVMContext.
allocLLVMFunPtrs :: forall sym bak (wptr :: Natural) (arch :: LLVMArch). (IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts :: MemOptions) => bak -> LLVMContext arch -> MemImpl sym -> Module -> IO (MemImpl sym) Source #
Create global allocations associated with each function in a module (see
allocLLVMFunPtr).
Arguments
| :: forall sym bak (wptr :: Natural). (IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts :: MemOptions) | |
| => bak | |
| -> MemImpl sym | |
| -> String | Display name |
| -> Symbol | Function name |
| -> [Symbol] | Aliases |
| -> IO (LLVMPtr sym wptr, MemImpl sym) |
Create a global allocation assocated with a function (see allocFunPtr),
and register the function's primary symbol and its aliases as associated
with that allocation.
Arguments
| :: forall sym bak (wptr :: Natural) (args :: Ctx CrucibleType) (ret :: CrucibleType). (IsSymBackend sym bak, HasPtrWidth wptr) | |
| => bak | |
| -> Symbol | Function name |
| -> FnHandle args ret | Function implementation (CFG or override) |
| -> MemImpl sym | LLVM memory |
| -> IO (MemImpl sym) |
Look up an existing global function allocation by name and bind a handle to it.
This can overwrite existing allocation/handle associations, and is used to do so when registering lazily-translated CFGs.
For a stateful version in OverrideSim, see bindLLVMHandle.
Arguments
| :: forall sym (wptr :: Natural) (args :: Ctx CrucibleType) (ret :: CrucibleType) p ext rtp (l :: Ctx CrucibleType) (a :: CrucibleType). (IsSymInterface sym, HasPtrWidth wptr) | |
| => GlobalVar Mem | |
| -> Symbol | Function name |
| -> FnHandle args ret | Function handle |
| -> FnState p sym ext args ret | Function implementation (CFG or override) |
| -> OverrideSim p sym ext rtp l a () |
Look up an existing global function allocation by name and bind a handle to it.
This can overwrite existing allocation/handle associations, and is used to do so when registering lazily-translated CFGs.
For a less stateful version in IO, see bindLLVMHandle.
Arguments
| :: forall sym (wptr :: Natural) (blocks :: Ctx (Ctx CrucibleType)) (init :: Ctx CrucibleType) (ret :: CrucibleType) p rtp (l :: Ctx CrucibleType) (a :: CrucibleType). (IsSymInterface sym, HasPtrWidth wptr) | |
| => GlobalVar Mem | |
| -> Symbol | Function name |
| -> CFG LLVM blocks init ret | Function CFG |
| -> OverrideSim p sym LLVM rtp l a () |
Look up an existing global function allocation by name and bind a CFG to it.
This can overwrite existing allocation/handle associations, and is used to do so when registering lazily-translated CFGs.
Arguments
| :: forall sym (wptr :: Natural) (args :: Ctx CrucibleType) (ret :: CrucibleType) p ext rtp (l :: Ctx CrucibleType) (a :: CrucibleType). (IsSymInterface sym, HasPtrWidth wptr) | |
| => GlobalVar Mem | |
| -> Symbol | Function name |
| -> Assignment TypeRepr args | Argument types |
| -> TypeRepr ret | Return type |
| -> FnState p sym ext args ret | Function implementation (CFG or override) |
| -> OverrideSim p sym ext rtp l a () |
Create a function handle, then call bindLLVMHandle on it.