Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Lang.Crucible.FunctionHandle
Synopsis
- data FnHandle (args :: Ctx CrucibleType) (ret :: CrucibleType)
- handleID :: FnHandle args ret -> Nonce GlobalNonceGenerator (args ::> ret)
- handleName :: FnHandle args ret -> FunctionName
- handleArgTypes :: FnHandle args ret -> CtxRepr args
- handleReturnType :: FnHandle args ret -> TypeRepr ret
- handleType :: FnHandle args ret -> TypeRepr (FunctionHandleType args ret)
- data SomeHandle where
- SomeHandle :: !(FnHandle args ret) -> SomeHandle
- data HandleAllocator
- haCounter :: HandleAllocator -> NonceGenerator IO GlobalNonceGenerator
- newHandleAllocator :: IO HandleAllocator
- withHandleAllocator :: (HandleAllocator -> IO a) -> IO a
- mkHandle :: (KnownCtx TypeRepr args, KnownRepr TypeRepr ret) => HandleAllocator -> FunctionName -> IO (FnHandle args ret)
- mkHandle' :: HandleAllocator -> FunctionName -> Assignment TypeRepr args -> TypeRepr ret -> IO (FnHandle args ret)
- data FnHandleMap f
- emptyHandleMap :: FnHandleMap f
- insertHandleMap :: FnHandle args ret -> f args ret -> FnHandleMap f -> FnHandleMap f
- lookupHandleMap :: FnHandle args ret -> FnHandleMap f -> Maybe (f args ret)
- updateHandleMap :: (f args ret -> f args ret) -> FnHandle args ret -> FnHandleMap f -> FnHandleMap f
- searchHandleMap :: FunctionName -> TypeRepr (FunctionHandleType args ret) -> FnHandleMap f -> Maybe (FnHandle args ret, f args ret)
- handleMapToHandles :: FnHandleMap f -> [SomeHandle]
- data RefCell (tp :: CrucibleType)
- freshRefCell :: HandleAllocator -> TypeRepr tp -> IO (RefCell tp)
- refType :: RefCell tp -> TypeRepr tp
Function handle
data FnHandle (args :: Ctx CrucibleType) (ret :: CrucibleType) Source #
A handle uniquely identifies a function. The signature indicates the expected argument types and the return type of the function.
Instances
LitExpr e (FunctionHandleType args ret) (FnHandle args ret) Source # | |
Defined in Lang.Crucible.Syntax Methods litExpr :: FnHandle args ret -> e (FunctionHandleType args ret) Source # | |
Show (FnHandle args ret) Source # | |
Eq (FnHandle args ret) Source # | |
Ord (FnHandle args ret) Source # | |
Defined in Lang.Crucible.FunctionHandle Methods compare :: FnHandle args ret -> FnHandle args ret -> Ordering # (<) :: FnHandle args ret -> FnHandle args ret -> Bool # (<=) :: FnHandle args ret -> FnHandle args ret -> Bool # (>) :: FnHandle args ret -> FnHandle args ret -> Bool # (>=) :: FnHandle args ret -> FnHandle args ret -> Bool # max :: FnHandle args ret -> FnHandle args ret -> FnHandle args ret # min :: FnHandle args ret -> FnHandle args ret -> FnHandle args ret # | |
Hashable (FnHandle args ret) Source # | |
Defined in Lang.Crucible.FunctionHandle |
handleID :: FnHandle args ret -> Nonce GlobalNonceGenerator (args ::> ret) Source #
A unique identifier for the function.
handleName :: FnHandle args ret -> FunctionName Source #
The name of the function (not necessarily unique)
handleArgTypes :: FnHandle args ret -> CtxRepr args Source #
The arguments types for the function
handleReturnType :: FnHandle args ret -> TypeRepr ret Source #
The return type of the function.
handleType :: FnHandle args ret -> TypeRepr (FunctionHandleType args ret) Source #
Return type of handle.
data SomeHandle where Source #
A function handle is a reference to a function in a given run of the simulator. It has a set of expected arguments and return type.
Constructors
SomeHandle :: !(FnHandle args ret) -> SomeHandle |
Instances
Show SomeHandle Source # | |
Defined in Lang.Crucible.FunctionHandle Methods showsPrec :: Int -> SomeHandle -> ShowS # show :: SomeHandle -> String # showList :: [SomeHandle] -> ShowS # | |
Eq SomeHandle Source # | |
Defined in Lang.Crucible.FunctionHandle | |
Ord SomeHandle Source # | |
Defined in Lang.Crucible.FunctionHandle Methods compare :: SomeHandle -> SomeHandle -> Ordering # (<) :: SomeHandle -> SomeHandle -> Bool # (<=) :: SomeHandle -> SomeHandle -> Bool # (>) :: SomeHandle -> SomeHandle -> Bool # (>=) :: SomeHandle -> SomeHandle -> Bool # max :: SomeHandle -> SomeHandle -> SomeHandle # min :: SomeHandle -> SomeHandle -> SomeHandle # | |
Hashable SomeHandle Source # | |
Defined in Lang.Crucible.FunctionHandle |
Allocate handle.
data HandleAllocator Source #
Used to allocate function handles.
newHandleAllocator :: IO HandleAllocator Source #
Create a new handle allocator.
withHandleAllocator :: (HandleAllocator -> IO a) -> IO a Source #
Create a new handle allocator and run the given computation.
mkHandle :: (KnownCtx TypeRepr args, KnownRepr TypeRepr ret) => HandleAllocator -> FunctionName -> IO (FnHandle args ret) Source #
Allocate a new function handle with requested args
and ret
types
mkHandle' :: HandleAllocator -> FunctionName -> Assignment TypeRepr args -> TypeRepr ret -> IO (FnHandle args ret) Source #
Allocate a new function handle.
FnHandleMap
data FnHandleMap f Source #
emptyHandleMap :: FnHandleMap f Source #
insertHandleMap :: FnHandle args ret -> f args ret -> FnHandleMap f -> FnHandleMap f Source #
lookupHandleMap :: FnHandle args ret -> FnHandleMap f -> Maybe (f args ret) Source #
Lookup the function specification in the map via the Nonce index in the FnHandle argument.
updateHandleMap :: (f args ret -> f args ret) -> FnHandle args ret -> FnHandleMap f -> FnHandleMap f Source #
Update the entry of the function handle in the map.
searchHandleMap :: FunctionName -> TypeRepr (FunctionHandleType args ret) -> FnHandleMap f -> Maybe (FnHandle args ret, f args ret) Source #
Lookup the function name in the map by a linear scan of all
entries. This will be much slower than using lookupHandleMap
to
find the function by ID, so the latter should be used if possible.
handleMapToHandles :: FnHandleMap f -> [SomeHandle] Source #
Reference cells
data RefCell (tp :: CrucibleType) Source #
Instances
TestEquality RefCell Source # | |
Defined in Lang.Crucible.FunctionHandle | |
OrdF RefCell Source # | |
Defined in Lang.Crucible.FunctionHandle Methods compareF :: forall (x :: k) (y :: k). RefCell x -> RefCell y -> OrderingF x y # leqF :: forall (x :: k) (y :: k). RefCell x -> RefCell y -> Bool # ltF :: forall (x :: k) (y :: k). RefCell x -> RefCell y -> Bool # geqF :: forall (x :: k) (y :: k). RefCell x -> RefCell y -> Bool # gtF :: forall (x :: k) (y :: k). RefCell x -> RefCell y -> Bool # | |
ShowF RefCell Source # | |
Show (RefCell tp) Source # | |
Eq (RefCell tp) Source # | |
Ord (RefCell tp) Source # | |
Defined in Lang.Crucible.FunctionHandle |
freshRefCell :: HandleAllocator -> TypeRepr tp -> IO (RefCell tp) Source #