crucible-llvm-0.6: Support for translating and executing LLVM code in Crucible
Copyright(c) Galois Inc 2011-2013
LicenseBSD3
MaintainerRob Dockins <rdockins@galois.com>
Stabilityprovisional
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lang.Crucible.LLVM.MemType

Description

 
Synopsis

Type information.

data SymType Source #

LLVM types supported by symbolic simulator.

Constructors

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.

Instances

Instances details
Show SymType Source # 
Instance details

Defined in Lang.Crucible.LLVM.MemType

Eq SymType Source # 
Instance details

Defined in Lang.Crucible.LLVM.MemType

Methods

(==) :: SymType -> SymType -> Bool #

(/=) :: SymType -> SymType -> Bool #

Ord SymType Source # 
Instance details

Defined in Lang.Crucible.LLVM.MemType

Pretty SymType Source # 
Instance details

Defined in Lang.Crucible.LLVM.MemType

Methods

pretty :: SymType -> Doc ann #

prettyList :: [SymType] -> Doc ann #

data MemType Source #

LLVM types supported by simulator with a defined size and alignment.

Constructors

IntType Natural 
PtrType SymType

A pointer with an explicit pointee type, corresponding to LLVM's PtrTo.

PtrOpaqueType

An opaque pointer type, corresponding to LLVM's PtrOpaque.

FloatType 
DoubleType 
X86_FP80Type 
ArrayType Natural MemType 
VecType Natural MemType 
StructType StructInfo 
MetadataType 

Instances

Instances details
Show MemType Source # 
Instance details

Defined in Lang.Crucible.LLVM.MemType

Eq MemType Source # 
Instance details

Defined in Lang.Crucible.LLVM.MemType

Methods

(==) :: MemType -> MemType -> Bool #

(/=) :: MemType -> MemType -> Bool #

Ord MemType Source # 
Instance details

Defined in Lang.Crucible.LLVM.MemType

Pretty MemType Source # 
Instance details

Defined in Lang.Crucible.LLVM.MemType

Methods

pretty :: MemType -> Doc ann #

prettyList :: [MemType] -> Doc ann #

memTypeAlign :: DataLayout -> MemType -> Alignment Source #

Returns ABI byte alignment constraint in bytes.

memTypeSize :: DataLayout -> MemType -> Bytes Source #

Returns size of a SymType in bytes.

ppSymType :: SymType -> Doc ann Source #

Pretty-print a SymType.

ppMemType :: MemType -> Doc ann Source #

Pretty-print a SymType.

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.

isPointerMemType :: MemType -> Bool Source #

Returns True if this is a pointer type.

Function type information.

data FunDecl Source #

An LLVM function type.

Constructors

FunDecl 

Instances

Instances details
Eq FunDecl Source # 
Instance details

Defined in Lang.Crucible.LLVM.MemType

Methods

(==) :: FunDecl -> FunDecl -> Bool #

(/=) :: FunDecl -> FunDecl -> Bool #

Ord FunDecl Source # 
Instance details

Defined in Lang.Crucible.LLVM.MemType

type RetType = Maybe MemType Source #

Return type if any.

voidFunDecl :: [MemType] -> FunDecl Source #

Declare function that returns void.

funDecl :: MemType -> [MemType] -> FunDecl Source #

Declare function that returns a value.

varArgsFunDecl :: MemType -> [MemType] -> FunDecl Source #

Declare function that returns a value.

ppFunDecl :: FunDecl -> Doc ann Source #

Pretty-print a function type.

ppRetType :: RetType -> Doc ann Source #

Pretty print a return type.

Struct type information.

data StructInfo Source #

Information about size, alignment, and fields of a struct.

mkStructInfo Source #

Arguments

:: DataLayout 
-> Bool

True = packed, False = unpacked

-> [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.

fiOffset :: FieldInfo -> Offset Source #

Byte offset of field relative to start of struct.

fiType :: FieldInfo -> MemType Source #

Type of field.

fiPadding :: FieldInfo -> Bytes Source #

Number of bytes of padding at end of field.

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.

i1 :: MemType Source #

1-bit integer type.

i8 :: MemType Source #

8-bit integer type.

i16 :: MemType Source #

16-bit integer type.

i32 :: MemType Source #

32-bit integer type.

i64 :: MemType Source #

64-bit integer type.

i8p :: MemType Source #

Pointer to 8-bit integer.

i16p :: MemType Source #

Pointer to 16-bit integer.

i32p :: MemType Source #

Pointer to 32-bit integer.

i64p :: MemType Source #

Pointer to 64-bit integer.

Re-exports

newtype Ident #

Constructors

Ident String 

Instances

Instances details
Data Ident 
Instance details

Defined in Text.LLVM.AST

Methods

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 #

toConstr :: Ident -> Constr #

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 
Instance details

Defined in Text.LLVM.AST

Methods

fromString :: String -> Ident #

Generic Ident 
Instance details

Defined in Text.LLVM.AST

Associated Types

type Rep Ident :: Type -> Type #

Methods

from :: Ident -> Rep Ident x #

to :: Rep Ident x -> Ident #

Show Ident 
Instance details

Defined in Text.LLVM.AST

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

Eq Ident 
Instance details

Defined in Text.LLVM.AST

Methods

(==) :: Ident -> Ident -> Bool #

(/=) :: Ident -> Ident -> Bool #

Ord Ident 
Instance details

Defined in Text.LLVM.AST

Methods

compare :: Ident -> Ident -> Ordering #

(<) :: Ident -> Ident -> Bool #

(<=) :: Ident -> Ident -> Bool #

(>) :: Ident -> Ident -> Bool #

(>=) :: Ident -> Ident -> Bool #

max :: Ident -> Ident -> Ident #

min :: Ident -> Ident -> Ident #

IsValue Ident 
Instance details

Defined in Text.LLVM

Methods

toValue :: Ident -> Value #

LLVMPretty Ident 
Instance details

Defined in Text.LLVM.PP

Methods

llvmPP :: Fmt Ident #

Lift Ident 
Instance details

Defined in Text.LLVM.AST

Methods

lift :: Quote m => Ident -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Ident -> Code m Ident #

DefineArgs Type (Typed Value -> BB ()) 
Instance details

Defined in Text.LLVM

Methods

defineBody :: [Typed Ident] -> Type -> (Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs as k => DefineArgs (Type :> as) (Typed Value -> k) 
Instance details

Defined in Text.LLVM

Methods

defineBody :: [Typed Ident] -> (Type :> as) -> (Typed Value -> k) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs (Type, Type) (Typed Value -> Typed Value -> BB ()) 
Instance details

Defined in Text.LLVM

Methods

defineBody :: [Typed Ident] -> (Type, Type) -> (Typed Value -> Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs (Type, Type, Type) (Typed Value -> Typed Value -> Typed Value -> BB ()) 
Instance details

Defined in Text.LLVM

Methods

defineBody :: [Typed Ident] -> (Type, Type, Type) -> (Typed Value -> Typed Value -> Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

type Rep Ident 
Instance details

Defined in Text.LLVM.AST

type Rep Ident = D1 ('MetaData "Ident" "Text.LLVM.AST" "llvm-pretty-0.12.0.0-IQ9WSqnPZAR7073gtLzbJu" 'True) (C1 ('MetaCons "Ident" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))