Copyright | (c) Galois Inc 2011-2013 |
---|---|
License | BSD3 |
Maintainer | Rob Dockins <rdockins@galois.com> |
Stability | provisional |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data SymType
- data MemType
- memTypeAlign :: DataLayout -> MemType -> Alignment
- memTypeSize :: DataLayout -> MemType -> Bytes
- ppSymType :: SymType -> Doc ann
- ppMemType :: MemType -> Doc ann
- memTypeBitwidth :: MemType -> Maybe Natural
- isPointerMemType :: MemType -> Bool
- data FunDecl = FunDecl {}
- type RetType = Maybe MemType
- voidFunDecl :: [MemType] -> FunDecl
- funDecl :: MemType -> [MemType] -> FunDecl
- varArgsFunDecl :: MemType -> [MemType] -> FunDecl
- ppFunDecl :: FunDecl -> Doc ann
- ppRetType :: RetType -> Doc ann
- data StructInfo
- siIsPacked :: StructInfo -> Bool
- mkStructInfo :: DataLayout -> Bool -> [MemType] -> StructInfo
- siFieldCount :: StructInfo -> Int
- data FieldInfo
- fiOffset :: FieldInfo -> Offset
- fiType :: FieldInfo -> MemType
- fiPadding :: FieldInfo -> Bytes
- siFieldInfo :: StructInfo -> Int -> Maybe FieldInfo
- siFieldTypes :: StructInfo -> Vector MemType
- siFieldOffset :: StructInfo -> Int -> Maybe Offset
- siFields :: StructInfo -> Vector FieldInfo
- siIndexOfOffset :: StructInfo -> Offset -> Maybe Int
- i1 :: MemType
- i8 :: MemType
- i16 :: MemType
- i32 :: MemType
- i64 :: MemType
- i8p :: MemType
- i16p :: MemType
- i32p :: MemType
- i64p :: MemType
- newtype Ident = Ident String
- ppIdent :: Ident -> Doc ann
Type information.
LLVM types supported by symbolic simulator.
MemType MemType | |
Alias Ident | |
FunType FunDecl | |
VoidType | |
OpaqueType | A type that LLVM does not know the structure of such as a struct that is declared, but not defined. |
UnsupportedType Type | A type not supported by the symbolic simulator. |
LLVM types supported by simulator with a defined size and alignment.
IntType Natural | |
PtrType SymType | A pointer with an explicit pointee type, corresponding to LLVM's
|
PtrOpaqueType | An opaque pointer type, corresponding to LLVM's |
FloatType | |
DoubleType | |
X86_FP80Type | |
ArrayType Natural MemType | |
VecType Natural MemType | |
StructType StructInfo | |
MetadataType |
memTypeAlign :: DataLayout -> MemType -> Alignment Source #
Returns ABI byte alignment constraint in bytes.
memTypeSize :: DataLayout -> MemType -> Bytes Source #
Returns size of a SymType
in bytes.
memTypeBitwidth :: MemType -> Maybe Natural Source #
Return the number of bits that represent the given memtype, which must be either integer types, floating point types or vectors of the same.
Function type information.
voidFunDecl :: [MemType] -> FunDecl Source #
Declare function that returns void.
Struct type information.
data StructInfo Source #
Information about size, alignment, and fields of a struct.
Instances
Show StructInfo Source # | |
Defined in Lang.Crucible.LLVM.MemType showsPrec :: Int -> StructInfo -> ShowS # show :: StructInfo -> String # showList :: [StructInfo] -> ShowS # | |
Eq StructInfo Source # | |
Defined in Lang.Crucible.LLVM.MemType (==) :: StructInfo -> StructInfo -> Bool # (/=) :: StructInfo -> StructInfo -> Bool # | |
Ord StructInfo Source # | |
Defined in Lang.Crucible.LLVM.MemType compare :: StructInfo -> StructInfo -> Ordering # (<) :: StructInfo -> StructInfo -> Bool # (<=) :: StructInfo -> StructInfo -> Bool # (>) :: StructInfo -> StructInfo -> Bool # (>=) :: StructInfo -> StructInfo -> Bool # max :: StructInfo -> StructInfo -> StructInfo # min :: StructInfo -> StructInfo -> StructInfo # |
siIsPacked :: StructInfo -> Bool Source #
:: DataLayout | |
-> Bool |
|
-> [MemType] | Field types |
-> StructInfo |
Constructs a function for obtaining target-specific size/alignment
information about structs. The function produced corresponds to the
StructLayout
object constructor in TargetData.cpp.
siFieldCount :: StructInfo -> Int Source #
Number of fields in a struct type.
siFieldInfo :: StructInfo -> Int -> Maybe FieldInfo Source #
Returns information for field with given index, if it is defined.
siFieldTypes :: StructInfo -> Vector MemType Source #
The types of a struct type's fields.
siFieldOffset :: StructInfo -> Int -> Maybe Offset Source #
Returns offset of field with given index, if it is defined.
siIndexOfOffset :: StructInfo -> Offset -> Maybe Int Source #
Returns index of field at the given byte offset (if any).
Common memory types.
Re-exports
Instances
Data Ident | |
Defined in Text.LLVM.AST gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ident -> c Ident # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ident # dataTypeOf :: Ident -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ident) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident) # gmapT :: (forall b. Data b => b -> b) -> Ident -> Ident # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r # gmapQ :: (forall d. Data d => d -> u) -> Ident -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ident -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ident -> m Ident # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ident -> m Ident # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ident -> m Ident # | |
IsString Ident | |
Defined in Text.LLVM.AST fromString :: String -> Ident # | |
Generic Ident | |
Show Ident | |
Eq Ident | |
Ord Ident | |
IsValue Ident | |
LLVMPretty Ident | |
Defined in Text.LLVM.PP | |
Lift Ident | |
DefineArgs Type (Typed Value -> BB ()) | |
DefineArgs as k => DefineArgs (Type :> as) (Typed Value -> k) | |
DefineArgs (Type, Type) (Typed Value -> Typed Value -> BB ()) | |
DefineArgs (Type, Type, Type) (Typed Value -> Typed Value -> Typed Value -> BB ()) | |
type Rep Ident | |
Defined in Text.LLVM.AST |