Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Cryptol.Backend.FFI
Description
The implementation of loading and calling external functions from shared libraries.
Synopsis
- data ForeignSrc
- getForeignSrcPath :: ForeignSrc -> Maybe FilePath
- loadForeignSrc :: FilePath -> IO (Either FFILoadError ForeignSrc)
- unloadForeignSrc :: ForeignSrc -> IO ()
- foreignLibPath :: FilePath -> IO (Maybe (FilePath, Bool))
- data ForeignImpl
- loadForeignImpl :: ForeignSrc -> String -> IO (Either FFILoadError ForeignImpl)
- class Storable a => FFIArg a
- class Storable a => FFIRet a
- data SomeFFIArg = forall a.FFIArg a => SomeFFIArg a
- callForeignImpl :: forall a. FFIRet a => ForeignImpl -> [SomeFFIArg] -> IO a
Documentation
data ForeignSrc Source #
A source from which we can retrieve implementations of foreign functions.
Instances
Show ForeignSrc Source # | |
Defined in Cryptol.Backend.FFI Methods showsPrec :: Int -> ForeignSrc -> ShowS # show :: ForeignSrc -> String # showList :: [ForeignSrc] -> ShowS # | |
NFData ForeignSrc Source # | |
Defined in Cryptol.Backend.FFI Methods rnf :: ForeignSrc -> () # |
getForeignSrcPath :: ForeignSrc -> Maybe FilePath Source #
Get the file path of the ForeignSrc
.
loadForeignSrc :: FilePath -> IO (Either FFILoadError ForeignSrc) Source #
Load a ForeignSrc
for the given Cryptol file path. The file path of
the shared library that we try to load is the same as the Cryptol file path
except with a platform specific extension.
unloadForeignSrc :: ForeignSrc -> IO () Source #
Explicitly unload a ForeignSrc
immediately instead of waiting for the
garbage collector to do it. This can be useful if you want to immediately
load the same library again to pick up new changes.
The ForeignSrc
must not be used in any way after this is called,
including calling ForeignImpl
s loaded from it.
foreignLibPath :: FilePath -> IO (Maybe (FilePath, Bool)) Source #
Given the path to a Cryptol module, compute the location of the shared library we'd like to load. If FFI is supported, returns the location and whether or not it actually exists on disk. Otherwise, returns Nothing.
data ForeignImpl Source #
An implementation of a foreign function.
loadForeignImpl :: ForeignSrc -> String -> IO (Either FFILoadError ForeignImpl) Source #
Load a ForeignImpl
with the given name from the given ForeignSrc
.
class Storable a => FFIArg a Source #
Types which can be converted into libffi arguments.
The Storable constraint is so that we can put them in arrays.
Minimal complete definition
ffiArg
Instances
FFIArg CDouble Source # | |
Defined in Cryptol.Backend.FFI | |
FFIArg CFloat Source # | |
Defined in Cryptol.Backend.FFI | |
FFIArg CSize Source # | |
Defined in Cryptol.Backend.FFI | |
FFIArg Word16 Source # | |
Defined in Cryptol.Backend.FFI | |
FFIArg Word32 Source # | |
Defined in Cryptol.Backend.FFI | |
FFIArg Word64 Source # | |
Defined in Cryptol.Backend.FFI | |
FFIArg Word8 Source # | |
Defined in Cryptol.Backend.FFI | |
FFIArg (Ptr a) Source # | |
Defined in Cryptol.Backend.FFI |
class Storable a => FFIRet a Source #
Types which can be returned from libffi.
The Storable constraint is so that we can put them in arrays.
Minimal complete definition
ffiRet
Instances
FFIRet CDouble Source # | |
Defined in Cryptol.Backend.FFI | |
FFIRet CFloat Source # | |
Defined in Cryptol.Backend.FFI | |
FFIRet Word16 Source # | |
Defined in Cryptol.Backend.FFI | |
FFIRet Word32 Source # | |
Defined in Cryptol.Backend.FFI | |
FFIRet Word64 Source # | |
Defined in Cryptol.Backend.FFI | |
FFIRet Word8 Source # | |
Defined in Cryptol.Backend.FFI | |
FFIRet () Source # | |
Defined in Cryptol.Backend.FFI |
data SomeFFIArg Source #
Existential wrapper around a FFIArg
.
Constructors
forall a.FFIArg a => SomeFFIArg a |
callForeignImpl :: forall a. FFIRet a => ForeignImpl -> [SomeFFIArg] -> IO a Source #
Call a ForeignImpl
with the given arguments. The type parameter decides
how the return value should be converted into a Haskell value.