Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Cryptol.TypeCheck.FFI.FFIType
Description
This module defines a nicer intermediate representation of Cryptol types allowed for the FFI, which the typechecker generates then stores in the AST. This way the FFI evaluation code does not have to examine the raw type signatures again.
Synopsis
- data FFIFunType = FFIFunType {
- ffiTParams :: [TParam]
- ffiArgTypes :: [FFIType]
- ffiRetType :: FFIType
- data FFIType
- data FFIBasicType
- data FFIBasicValType
- data FFIWordSize
- data FFIFloatSize
- data FFIBasicRefType
- = FFIInteger (Maybe Type)
- | FFIRational
Documentation
data FFIFunType Source #
Type of a foreign function.
Constructors
FFIFunType | |
Fields
|
Instances
Type of a value that can be passed to or returned from a foreign function.
Constructors
FFIBool | |
FFIBasic FFIBasicType | |
FFIArray [Type] FFIBasicType |
|
FFITuple [FFIType] | |
FFIRecord (RecordMap Ident FFIType) |
Instances
data FFIBasicType Source #
Types which can be elements of FFI arrays.
Constructors
FFIBasicVal FFIBasicValType | |
FFIBasicRef FFIBasicRefType |
Instances
Generic FFIBasicType Source # | |
Defined in Cryptol.TypeCheck.FFI.FFIType Associated Types type Rep FFIBasicType :: Type -> Type # | |
Show FFIBasicType Source # | |
Defined in Cryptol.TypeCheck.FFI.FFIType Methods showsPrec :: Int -> FFIBasicType -> ShowS # show :: FFIBasicType -> String # showList :: [FFIBasicType] -> ShowS # | |
NFData FFIBasicType Source # | |
Defined in Cryptol.TypeCheck.FFI.FFIType Methods rnf :: FFIBasicType -> () # | |
type Rep FFIBasicType Source # | |
Defined in Cryptol.TypeCheck.FFI.FFIType type Rep FFIBasicType = D1 ('MetaData "FFIBasicType" "Cryptol.TypeCheck.FFI.FFIType" "cryptol-3.3.0-7OIQa8lMv7L2xoAlM9JEI6" 'False) (C1 ('MetaCons "FFIBasicVal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FFIBasicValType)) :+: C1 ('MetaCons "FFIBasicRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FFIBasicRefType))) |
data FFIBasicValType Source #
Basic type which is passed and returned directly by value.
Constructors
FFIWord | |
Fields
| |
FFIFloat | |
Fields
|
Instances
data FFIWordSize Source #
Instances
Generic FFIWordSize Source # | |
Defined in Cryptol.TypeCheck.FFI.FFIType Associated Types type Rep FFIWordSize :: Type -> Type # | |
Show FFIWordSize Source # | |
Defined in Cryptol.TypeCheck.FFI.FFIType Methods showsPrec :: Int -> FFIWordSize -> ShowS # show :: FFIWordSize -> String # showList :: [FFIWordSize] -> ShowS # | |
NFData FFIWordSize Source # | |
Defined in Cryptol.TypeCheck.FFI.FFIType Methods rnf :: FFIWordSize -> () # | |
type Rep FFIWordSize Source # | |
Defined in Cryptol.TypeCheck.FFI.FFIType type Rep FFIWordSize = D1 ('MetaData "FFIWordSize" "Cryptol.TypeCheck.FFI.FFIType" "cryptol-3.3.0-7OIQa8lMv7L2xoAlM9JEI6" 'False) ((C1 ('MetaCons "FFIWord8" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FFIWord16" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FFIWord32" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FFIWord64" 'PrefixI 'False) (U1 :: Type -> Type))) |
data FFIFloatSize Source #
Constructors
FFIFloat32 | |
FFIFloat64 |
Instances
Generic FFIFloatSize Source # | |
Defined in Cryptol.TypeCheck.FFI.FFIType Associated Types type Rep FFIFloatSize :: Type -> Type # | |
Show FFIFloatSize Source # | |
Defined in Cryptol.TypeCheck.FFI.FFIType Methods showsPrec :: Int -> FFIFloatSize -> ShowS # show :: FFIFloatSize -> String # showList :: [FFIFloatSize] -> ShowS # | |
NFData FFIFloatSize Source # | |
Defined in Cryptol.TypeCheck.FFI.FFIType Methods rnf :: FFIFloatSize -> () # | |
type Rep FFIFloatSize Source # | |
Defined in Cryptol.TypeCheck.FFI.FFIType |
data FFIBasicRefType Source #
Basic type which is passed and returned by reference through a parameter.
Constructors
FFIInteger (Maybe Type) | Modulus (Just for Z, Nothing for Integer) |
FFIRational |
Instances
Generic FFIBasicRefType Source # | |
Defined in Cryptol.TypeCheck.FFI.FFIType Associated Types type Rep FFIBasicRefType :: Type -> Type # Methods from :: FFIBasicRefType -> Rep FFIBasicRefType x # to :: Rep FFIBasicRefType x -> FFIBasicRefType # | |
Show FFIBasicRefType Source # | |
Defined in Cryptol.TypeCheck.FFI.FFIType Methods showsPrec :: Int -> FFIBasicRefType -> ShowS # show :: FFIBasicRefType -> String # showList :: [FFIBasicRefType] -> ShowS # | |
NFData FFIBasicRefType Source # | |
Defined in Cryptol.TypeCheck.FFI.FFIType Methods rnf :: FFIBasicRefType -> () # | |
type Rep FFIBasicRefType Source # | |
Defined in Cryptol.TypeCheck.FFI.FFIType type Rep FFIBasicRefType = D1 ('MetaData "FFIBasicRefType" "Cryptol.TypeCheck.FFI.FFIType" "cryptol-3.3.0-7OIQa8lMv7L2xoAlM9JEI6" 'False) (C1 ('MetaCons "FFIInteger" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Type))) :+: C1 ('MetaCons "FFIRational" 'PrefixI 'False) (U1 :: Type -> Type)) |