Safe Haskell | None |
---|---|
Language | Haskell2010 |
LLVM.General.Quote.AST
- data Module = Module {}
- data Definition
- data Global
- = GlobalVariable {
- name :: Name
- linkage :: Linkage
- visibility :: Visibility
- isThreadLocal :: Bool
- addrSpace :: AddrSpace
- hasUnnamedAddr :: Bool
- isConstant :: Bool
- _type' :: Type
- initializer :: Maybe Constant
- section :: Maybe String
- alignmentG :: Word32
- | GlobalAlias { }
- | Function {
- linkage :: Linkage
- visibility :: Visibility
- _callingConvention :: CallingConvention
- _returnAttributes :: [ParameterAttribute]
- returnType :: Type
- name :: Name
- parameters :: ([Parameter], Bool)
- _functionAttributes :: [FunctionAttribute]
- section :: Maybe String
- alignment :: Word32
- garbageCollectorName :: Maybe String
- instructions :: [LabeledInstruction]
- = GlobalVariable {
- data Parameter
- = Parameter Type Name [ParameterAttribute]
- | AntiParameter String
- | AntiParameterList String
- data Direction
- type InstructionMetadata = [(String, MetadataNode)]
- data LandingPadClause
- data FastMathFlags
- = NoFastMathFlags
- | UnsafeAlgebra
- | FastMathFlags {
- noNaNs :: Bool
- noInfs :: Bool
- noSignedZeros :: Bool
- allowReciprocal :: Bool
- data Instruction
- = Add { }
- | FAdd { }
- | Sub { }
- | FSub { }
- | Mul { }
- | FMul { }
- | UDiv { }
- | SDiv { }
- | FDiv { }
- | URem { }
- | SRem { }
- | FRem { }
- | Shl { }
- | LShr { }
- | AShr { }
- | And { }
- | Or { }
- | Xor { }
- | Alloca { }
- | Load {
- volatile :: Bool
- address :: Operand
- maybeAtomicity :: Maybe Atomicity
- alignmentI :: Word32
- metadata :: InstructionMetadata
- | Store {
- volatile :: Bool
- address :: Operand
- value :: Operand
- maybeAtomicity :: Maybe Atomicity
- alignmentI :: Word32
- metadata :: InstructionMetadata
- | GetElementPtr { }
- | Fence {
- atomicity :: Atomicity
- metadata :: InstructionMetadata
- | CmpXchg { }
- | AtomicRMW {
- volatile :: Bool
- rmwOperation :: RMWOperation
- address :: Operand
- value :: Operand
- atomicity :: Atomicity
- metadata :: InstructionMetadata
- | Trunc { }
- | ZExt { }
- | SExt { }
- | FPToUI { }
- | FPToSI { }
- | UIToFP { }
- | SIToFP { }
- | FPTrunc { }
- | FPExt { }
- | PtrToInt { }
- | IntToPtr { }
- | BitCast { }
- | AddrSpaceCast { }
- | ICmp {
- iPredicate :: IntegerPredicate
- operand0 :: Operand
- operand1 :: Operand
- metadata :: InstructionMetadata
- | FCmp {
- fpPredicate :: FloatingPointPredicate
- operand0 :: Operand
- operand1 :: Operand
- metadata :: InstructionMetadata
- | Phi {
- type' :: Type
- incomingValues :: [(Operand, Name)]
- metadata :: InstructionMetadata
- | Call {
- isTailCall :: Bool
- callingConvention :: CallingConvention
- returnAttributes :: [ParameterAttribute]
- function :: CallableOperand
- arguments :: [(Operand, [ParameterAttribute])]
- functionAttributes :: [FunctionAttribute]
- metadata :: InstructionMetadata
- | Select { }
- | VAArg { }
- | ExtractElement { }
- | InsertElement { }
- | ShuffleVector { }
- | ExtractValue { }
- | InsertValue { }
- | LandingPad { }
- | AntiInstruction String
- | Ret { }
- | CondBr { }
- | Br { }
- | Switch {
- operand0' :: Operand
- defaultDest :: Name
- dests :: [(Constant, Name)]
- metadata' :: InstructionMetadata
- | IndirectBr { }
- | Invoke {
- callingConvention' :: CallingConvention
- returnAttributes' :: [ParameterAttribute]
- function' :: CallableOperand
- arguments' :: [(Operand, [ParameterAttribute])]
- functionAttributes' :: [FunctionAttribute]
- returnDest :: Name
- exceptionDest :: Name
- metadata :: InstructionMetadata
- | Resume { }
- | Unreachable { }
- | OperandInstruction Operand
- data NamedInstruction
- data LabeledInstruction
- newtype MetadataNodeID = MetadataNodeID Word
- data MetadataNode
- data Operand
- type CallableOperand = Either InlineAssembly Operand
- data Constant
- = Int { }
- | IntAntiBs { }
- | Float {
- floatValue :: SomeFloat
- | Null {
- constantType :: Type
- | Struct {
- structName :: Maybe Name
- _isPacked :: Bool
- memberValues :: [Constant]
- | Array {
- memberType :: Type
- memberValues :: [Constant]
- | Vector {
- memberValues :: [Constant]
- | Undef {
- constantType :: Type
- | BlockAddress { }
- | GlobalReference Type Name
- | AntiConstant String
- data Name
- data Type
- = VoidType
- | IntegerType { }
- | PointerType {
- pointerReferent :: Type
- pointerAddrSpace :: AddrSpace
- | FloatingPointType {
- typeBits :: Word32
- floatingPointFormat :: FloatingPointFormat
- | FunctionType {
- resultType :: Type
- argumentTypes :: [Type]
- isVarArg :: Bool
- | VectorType { }
- | StructureType {
- isPacked :: Bool
- elementTypes :: [Type]
- | ArrayType { }
- | NamedTypeReference Name
- | MetadataType
- | AntiType String
- data InlineAssembly = InlineAssembly {
- __type' :: Type
- assembly :: String
- constraints :: String
- hasSideEffects :: Bool
- alignStack :: Bool
- dialect :: Dialect
- data DataLayout
- = DataLayout {
- endianness :: Maybe Endianness
- stackAlignment :: Maybe Word32
- pointerLayouts :: Map AddrSpace (Word32, AlignmentInfo)
- typeLayouts :: Map (AlignType, Word32) AlignmentInfo
- nativeSizes :: Maybe (Set Word32)
- | AntiDataLayout String
- = DataLayout {
- data TargetTriple
- data Extensions
- type ExtensionsInt = Word32
Documentation
Constructors
Module | |
Fields
|
data Definition Source
Any thing which can be at the top level of a Module
Constructors
Instances
Constructors
GlobalVariable | |
Fields
| |
GlobalAlias | |
Function | |
Fields
|
Constructors
Parameter Type Name [ParameterAttribute] | |
AntiParameter String | |
AntiParameterList String |
type InstructionMetadata = [(String, MetadataNode)] Source
http://llvm.org/docs/LangRef.html#metadata-nodes-and-metadata-strings Metadata can be attached to an instruction
data LandingPadClause Source
For the redoubtably complex LandingPad
instruction
data FastMathFlags Source
Constructors
NoFastMathFlags | |
UnsafeAlgebra | |
FastMathFlags | |
Fields
|
data Instruction Source
non-terminator instructions: http://llvm.org/docs/LangRef.html#binaryops http://llvm.org/docs/LangRef.html#bitwiseops http://llvm.org/docs/LangRef.html#memoryops http://llvm.org/docs/LangRef.html#otherops
Constructors
data NamedInstruction Source
Instances of instructions may be given a name, allowing their results to be referenced as Operand
s.
Sometimes instructions - e.g. a call to a function returning void - don't need names.
data LabeledInstruction Source
Constructors
Labeled | |
Fields
| |
ForLoop | |
ITE | |
Fields
| |
While | |
newtype MetadataNodeID Source
A MetadataNodeID
is a number for identifying a metadata node.
Note this is different from "named metadata", which are represented with
NamedMetadataDefinition
.
Constructors
MetadataNodeID Word |
data MetadataNode Source
Constructors
MetadataNode [Maybe Operand] | |
MetadataNodeReference MetadataNodeID |
An Operand
is roughly that which is an argument to an Instruction
Constructors
LocalReference Type Name | %foo |
ConstantOperand Constant |
|
MetadataStringOperand String | |
MetadataNodeOperand MetadataNode | |
AntiOperand String |
type CallableOperand = Either InlineAssembly Operand Source
The Call
instruction is special: the callee can be inline assembly
http://llvm.org/docs/LangRef.html#constants
N.B. - http://llvm.org/docs/LangRef.html#constant-expressions
Although constant expressions and instructions have many similarites, there are important differences - so they're represented using different types in this AST. At the cost of making it harder to move an code back and forth between being constant and not, this approach embeds more of the rules of what IR is legal into the Haskell types.
Constructors
Int | |
Fields
| |
IntAntiBs | |
Fields | |
Float | |
Fields
| |
Null | |
Fields
| |
Struct | |
Fields
| |
Array | |
Fields
| |
Vector | |
Fields
| |
Undef | |
Fields
| |
BlockAddress | |
Fields | |
GlobalReference Type Name | |
AntiConstant String |
Objects of various sorts in LLVM IR are identified by address in the LLVM C++ API, and may be given a string name. When printed to (resp. read from) human-readable LLVM assembly, objects without string names are numbered sequentially (resp. must be numbered sequentially). String names may be quoted, and are quoted when printed if they would otherwise be misread - e.g. when containing special characters.
7
means the seventh unnamed object, while
"7"
means the object named with the string "7".
This libraries handling of UnName
s during translation of the AST down into C++ IR is somewhat more
forgiving than the LLVM assembly parser: it does not require that unnamed values be numbered sequentially;
however, the numbers of UnName
s passed into C++ cannot be preserved in the C++ objects. If the C++ IR is
printed as assembly or translated into a Haskell AST, unnamed nodes will be renumbered sequentially. Thus
unnamed node numbers should be thought of as having any scope limited to the Module
in
which they are used.
Constructors
VoidType | |
IntegerType | |
PointerType | |
Fields
| |
FloatingPointType | |
Fields
| |
FunctionType | |
Fields
| |
VectorType | |
Fields
| |
StructureType | |
Fields
| |
ArrayType | |
Fields
| |
NamedTypeReference Name | |
MetadataType | |
AntiType String |
data InlineAssembly Source
http://llvm.org/docs/LangRef.html#inline-assembler-expressions
to be used through CallableOperand
with a
Call
instruction
Constructors
InlineAssembly | |
Fields
|
data DataLayout Source
a description of the various data layout properties which may be used during optimization
Constructors
DataLayout | |
Fields
| |
AntiDataLayout String |
data TargetTriple Source
Constructors
NoTargetTriple | |
TargetTriple String | |
AntiTargetTriple String |
type ExtensionsInt = Word32 Source