llvm-tf-9.1.1: Bindings to the LLVM compiler toolkit using type families.

Safe HaskellNone

LLVM.Core

Contents

Description

The LLVM (Low Level Virtual Machine) is virtual machine at a machine code level. It supports both stand alone code generation and JITing. The Haskell llvm package is a (relatively) high level interface to the LLVM. The high level interface makes it easy to construct LLVM code. There is also an interface to the raw low level LLVM API as exposed by the LLVM C interface.

LLVM code is organized into modules (type Module). Each module contains a number of global variables and functions (type Function). Each functions has a number of basic blocks (type BasicBlock). Each basic block has a number instructions, where each instruction produces a value (type Value).

Unlike assembly code for a real processor the assembly code for LLVM is in SSA (Static Single Assignment) form. This means that each instruction generates a new bound variable which may not be assigned again. A consequence of this is that where control flow joins from several execution paths there has to be a phi pseudo instruction if you want different variables to be joined into one.

The definition of several of the LLVM entities (Module, Function, and BasicBlock) follow the same pattern. First the entity has to be created using newX (where X is one of Module, Function, or BasicBlock), then at some later point it has to given its definition using defineX. The reason for splitting the creation and definition is that you often need to be able to refer to an entity before giving it's body, e.g., in two mutually recursive functions. The the newX and defineX function can also be done at the same time by using createX. Furthermore, an explicit name can be given to an entity by the newNamedX function; the newX function just generates a fresh name.

Synopsis

Initialize

initializeNativeTarget :: IO ()

Initialize jitter to the native target. The operation is idempotent.

Modules

data Module Source

Type of top level modules.

newModule :: IO ModuleSource

Create a new module.

newNamedModuleSource

Arguments

:: String

module name

-> IO Module 

Create a new explicitely named module.

defineModuleSource

Arguments

:: Module

module that is defined

-> CodeGenModule a

module body

-> IO a 

Give the body for a module.

destroyModule :: Module -> IO ()Source

Free all storage related to a module. *Note*, this is a dangerous call, since referring to the module after this call is an error. The reason for the explicit call to free the module instead of an automatic lifetime management is that modules have a somewhat complicated ownership. Handing a module to a module provider changes the ownership of the module, and the module provider will free the module when necessary.

createModuleSource

Arguments

:: CodeGenModule a

module body

-> IO a 

Create a new module with the given body.

data PassManager Source

Manage compile passes.

createPassManager :: IO PassManagerSource

Create a pass manager.

createFunctionPassManager :: Module -> IO PassManagerSource

Create a pass manager for a module.

writeBitcodeToFile :: String -> Module -> IO ()Source

Write a module to a file.

readBitcodeFromFile :: String -> IO ModuleSource

Read a module from a file.

Instructions

ADT representation of IR

data ArgDesc Source

Constructors

AV String 
AI Int 
AL String 
AE 

Instances

Terminator instructions

ret :: Ret a r => a -> CodeGenFunction r TerminateSource

Return from the current function with the given value. Use () as the return value for what would be a void function in C.

condBrSource

Arguments

:: Value Bool

Boolean to branch upon.

-> BasicBlock

Target for true.

-> BasicBlock

Target for false.

-> CodeGenFunction r Terminate 

Branch to the first basic block if the boolean is true, otherwise to the second basic block.

brSource

Arguments

:: BasicBlock

Branch target.

-> CodeGenFunction r Terminate 

Unconditionally branch to the given basic block.

switchSource

Arguments

:: IsInteger a 
=> Value a

Value to branch upon.

-> BasicBlock

Default branch target.

-> [(ConstValue a, BasicBlock)]

Labels and corresponding branch targets.

-> CodeGenFunction r Terminate 

Branch table instruction.

invokeSource

Arguments

:: CallArgs f g r 
=> BasicBlock

Normal return point.

-> BasicBlock

Exception return point.

-> Function f

Function to call.

-> g 

Call a function with exception handling.

invokeWithConvSource

Arguments

:: CallArgs f g r 
=> CallingConvention

Calling convention

-> BasicBlock

Normal return point.

-> BasicBlock

Exception return point.

-> Function f

Function to call.

-> g 

Call a function with exception handling. This also sets the calling convention of the call to the function. As LLVM itself defines, if the calling conventions of the calling instruction and the function being called are different, undefined behavior results.

invokeFromFunctionSource

Arguments

:: BasicBlock

Normal return point.

-> BasicBlock

Exception return point.

-> Function f

Function to call.

-> Call f 

invokeWithConvFromFunctionSource

Arguments

:: CallingConvention

Calling convention

-> BasicBlock

Normal return point.

-> BasicBlock

Exception return point.

-> Function f

Function to call.

-> Call f 

unreachable :: CodeGenFunction r TerminateSource

Inform the code generator that this code can never be reached.

Arithmetic binary operations

Arithmetic operations with the normal semantics. The u instructions are unsigned, the s instructions are signed.

add :: (ValueCons2 value0 value1, IsArithmetic a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

sub :: (ValueCons2 value0 value1, IsArithmetic a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

mul :: (ValueCons2 value0 value1, IsArithmetic a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

neg :: (ValueCons value, IsArithmetic a) => value a -> CodeGenFunction r (value a)Source

iadd :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

isub :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

imul :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

ineg :: (ValueCons value, IsInteger a) => value a -> CodeGenFunction r (value a)Source

iaddNoWrap :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

isubNoWrap :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

imulNoWrap :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

inegNoWrap :: forall value a r. (ValueCons value, IsInteger a) => value a -> CodeGenFunction r (value a)Source

fadd :: (ValueCons2 value0 value1, IsFloating a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

fsub :: (ValueCons2 value0 value1, IsFloating a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

fmul :: (ValueCons2 value0 value1, IsFloating a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

fneg :: (ValueCons value, IsFloating a) => value a -> CodeGenFunction r (value a)Source

idiv :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

signed or unsigned integer division depending on the type

irem :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

signed or unsigned remainder depending on the type

udiv :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

Deprecated: use idiv instead

sdiv :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

Deprecated: use idiv instead

fdiv :: (ValueCons2 value0 value1, IsFloating a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

Floating point division.

urem :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

Deprecated: use irem instead

srem :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

Deprecated: use irem instead

frem :: (ValueCons2 value0 value1, IsFloating a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

Floating point remainder.

Logical binary operations

Logical instructions with the normal semantics.

shl :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

shr :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

lshr :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

ashr :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

and :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

or :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

xor :: (ValueCons2 value0 value1, IsInteger a) => value0 a -> value1 a -> CodeGenFunction r (BinOpValue value0 value1 a)Source

inv :: (ValueCons value, IsInteger a) => value a -> CodeGenFunction r (value a)Source

Vector operations

extractelementSource

Arguments

:: (Positive n, IsPrimitive a) 
=> Value (Vector n a)

Vector

-> Value Word32

Index into the vector

-> CodeGenFunction r (Value a) 

Get a value from a vector.

insertelementSource

Arguments

:: (Positive n, IsPrimitive a) 
=> Value (Vector n a)

Vector

-> Value a

Value to insert

-> Value Word32

Index into the vector

-> CodeGenFunction r (Value (Vector n a)) 

Insert a value into a vector, nondestructive.

shufflevector :: (Positive n, Positive m, IsPrimitive a) => Value (Vector n a) -> Value (Vector n a) -> ConstValue (Vector m Word32) -> CodeGenFunction r (Value (Vector m a))Source

Permute vector.

Aggregate operation

extractvalueSource

Arguments

:: forall r agg i . GetValue agg i 
=> Value agg

Aggregate

-> i

Index into the aggregate

-> CodeGenFunction r (Value (ValueType agg i)) 

Get a value from an aggregate.

insertvalueSource

Arguments

:: forall r agg i . GetValue agg i 
=> Value agg

Aggregate

-> Value (ValueType agg i)

Value to insert

-> i

Index into the aggregate

-> CodeGenFunction r (Value agg) 

Insert a value into an aggregate, nondestructive.

Memory access

malloc :: forall a r. IsSized a => CodeGenFunction r (Value (Ptr a))Source

Allocate heap memory.

arrayMalloc :: forall a r s. (IsSized a, AllocArg s) => s -> CodeGenFunction r (Value (Ptr a))Source

Allocate heap (array) memory.

alloca :: forall a r. IsSized a => CodeGenFunction r (Value (Ptr a))Source

Allocate stack memory.

arrayAlloca :: forall a r s. (IsSized a, AllocArg s) => s -> CodeGenFunction r (Value (Ptr a))Source

Allocate stack (array) memory.

free :: IsType a => Value (Ptr a) -> CodeGenFunction r ()Source

Free heap memory.

loadSource

Arguments

:: Value (Ptr a)

Address to load from.

-> CodeGenFunction r (Value a) 

Load a value from memory.

storeSource

Arguments

:: Value a

Value to store.

-> Value (Ptr a)

Address to store to.

-> CodeGenFunction r () 

Store a value in memory

getElementPtr :: forall a o i r. (GetElementPtr o i, IsIndexArg a) => Value (Ptr o) -> (a, i) -> CodeGenFunction r (Value (Ptr (ElementPtrType o i)))Source

Address arithmetic. See LLVM description. The index is a nested tuple of the form (i1,(i2,( ... ()))). (This is without a doubt the most confusing LLVM instruction, but the types help.)

getElementPtr0 :: GetElementPtr o i => Value (Ptr o) -> i -> CodeGenFunction r (Value (Ptr (ElementPtrType o i)))Source

Like getElementPtr, but with an initial index that is 0. This is useful since any pointer first need to be indexed off the pointer, and then into its actual value. This first indexing is often with 0.

Conversions

trunc :: (ValueCons value, IsInteger a, IsInteger b, ShapeOf a ~ ShapeOf b, IsSized a, IsSized b, SizeOf a :>: SizeOf b) => value a -> CodeGenFunction r (value b)Source

Truncate a value to a shorter bit width.

zext :: (ValueCons value, IsInteger a, IsInteger b, ShapeOf a ~ ShapeOf b, IsSized a, IsSized b, SizeOf a :<: SizeOf b) => value a -> CodeGenFunction r (value b)Source

Zero extend a value to a wider width. If possible, use ext that chooses the right padding according to the types

sext :: (ValueCons value, IsInteger a, IsInteger b, ShapeOf a ~ ShapeOf b, IsSized a, IsSized b, SizeOf a :<: SizeOf b) => value a -> CodeGenFunction r (value b)Source

Sign extend a value to wider width. If possible, use ext that chooses the right padding according to the types

ext :: forall value a b r. (ValueCons value, IsInteger a, IsInteger b, ShapeOf a ~ ShapeOf b, Signed a ~ Signed b, IsSized a, IsSized b, SizeOf a :<: SizeOf b) => value a -> CodeGenFunction r (value b)Source

Extend a value to wider width. If the target type is signed, then preserve the sign, If the target type is unsigned, then extended by zeros.

zadapt :: forall value a b r. (ValueCons value, IsInteger a, IsInteger b, ShapeOf a ~ ShapeOf b) => value a -> CodeGenFunction r (value b)Source

It is zext, trunc or nop depending on the relation of the sizes.

sadapt :: forall value a b r. (ValueCons value, IsInteger a, IsInteger b, ShapeOf a ~ ShapeOf b) => value a -> CodeGenFunction r (value b)Source

It is sext, trunc or nop depending on the relation of the sizes.

adapt :: forall value a b r. (ValueCons value, IsInteger a, IsInteger b, ShapeOf a ~ ShapeOf b, Signed a ~ Signed b) => value a -> CodeGenFunction r (value b)Source

It is sadapt or zadapt depending on the sign mode.

fptrunc :: (ValueCons value, IsFloating a, IsFloating b, ShapeOf a ~ ShapeOf b, IsSized a, IsSized b, SizeOf a :>: SizeOf b) => value a -> CodeGenFunction r (value b)Source

Truncate a floating point value.

fpext :: (ValueCons value, IsFloating a, IsFloating b, ShapeOf a ~ ShapeOf b, IsSized a, IsSized b, SizeOf a :<: SizeOf b) => value a -> CodeGenFunction r (value b)Source

Extend a floating point value.

fptoui :: (ValueCons value, IsFloating a, IsInteger b, ShapeOf a ~ ShapeOf b) => value a -> CodeGenFunction r (value b)Source

Deprecated: use fptoint since it is type-safe with respect to signs

Convert a floating point value to an unsigned integer.

fptosi :: (ValueCons value, IsFloating a, IsInteger b, ShapeOf a ~ ShapeOf b) => value a -> CodeGenFunction r (value b)Source

Deprecated: use fptoint since it is type-safe with respect to signs

Convert a floating point value to a signed integer.

fptoint :: forall value a b r. (ValueCons value, IsFloating a, IsInteger b, ShapeOf a ~ ShapeOf b) => value a -> CodeGenFunction r (value b)Source

Convert a floating point value to an integer. It is mapped to fptosi or fptoui depending on the type a.

uitofp :: (ValueCons value, IsInteger a, IsFloating b, ShapeOf a ~ ShapeOf b) => value a -> CodeGenFunction r (value b)Source

Convert an unsigned integer to a floating point value. Although inttofp should be prefered, this function may be useful for conversion from Bool.

sitofp :: (ValueCons value, IsInteger a, IsFloating b, ShapeOf a ~ ShapeOf b) => value a -> CodeGenFunction r (value b)Source

Convert a signed integer to a floating point value. Although inttofp should be prefered, this function may be useful for conversion from Bool.

inttofp :: forall value a b r. (ValueCons value, IsInteger a, IsFloating b, ShapeOf a ~ ShapeOf b) => value a -> CodeGenFunction r (value b)Source

Convert an integer to a floating point value. It is mapped to sitofp or uitofp depending on the type a.

ptrtoint :: (ValueCons value, IsInteger b, IsPrimitive b) => value (Ptr a) -> CodeGenFunction r (value b)Source

Convert a pointer to an integer.

inttoptr :: (ValueCons value, IsInteger a, IsType b) => value a -> CodeGenFunction r (value (Ptr b))Source

Convert an integer to a pointer.

bitcast :: (ValueCons value, IsFirstClass a, IsFirstClass b, IsSized a, IsSized b, SizeOf a ~ SizeOf b) => value a -> CodeGenFunction r (value b)Source

Convert between to values of the same size by just copying the bit pattern.

Comparison

data CmpPredicate Source

Constructors

CmpEQ

equal

CmpNE

not equal

CmpGT

greater than

CmpGE

greater or equal

CmpLT

less than

CmpLE

less or equal

data IntPredicate

Constructors

IntEQ

equal

IntNE

not equal

IntUGT

unsigned greater than

IntUGE

unsigned greater or equal

IntULT

unsigned less than

IntULE

unsigned less or equal

IntSGT

signed greater than

IntSGE

signed greater or equal

IntSLT

signed less than

IntSLE

signed less or equal

data FPPredicate

Constructors

FPFalse

Always false (always folded)

FPOEQ

True if ordered and equal

FPOGT

True if ordered and greater than

FPOGE

True if ordered and greater than or equal

FPOLT

True if ordered and less than

FPOLE

True if ordered and less than or equal

FPONE

True if ordered and operands are unequal

FPORD

True if ordered (no nans)

FPUNO

True if unordered: isnan(X) | isnan(Y)

FPUEQ

True if unordered or equal

FPUGT

True if unordered or greater than

FPUGE

True if unordered, greater than, or equal

FPULT

True if unordered or less than

FPULE

True if unordered, less than, or equal

FPUNE

True if unordered or not equal

FPTrue

Always true (always folded)

type CmpValueResult value0 value1 a = BinOpValue value0 value1 (CmpResult a)Source

cmp :: forall value0 value1 a r. (ValueCons2 value0 value1, CmpRet a) => CmpPredicate -> value0 a -> value1 a -> CodeGenFunction r (CmpValueResult value0 value1 a)Source

Compare values of ordered types and choose predicates according to the compared types. Floating point numbers are compared in "ordered" mode, that is NaN operands yields False as result. Pointers are compared unsigned. These choices are consistent with comparison in plain Haskell.

pcmp :: (ValueCons2 value0 value1, IsType a) => IntPredicate -> value0 (Ptr a) -> value1 (Ptr a) -> CodeGenFunction r (BinOpValue value0 value1 (Ptr a))Source

icmp :: (ValueCons2 value0 value1, CmpRet a, IsIntegerOrPointer a) => IntPredicate -> value0 a -> value1 a -> CodeGenFunction r (CmpValueResult value0 value1 a)Source

Deprecated: use cmp or pcmp instead

Compare integers.

fcmp :: (ValueCons2 value0 value1, CmpRet a, IsFloating a) => FPPredicate -> value0 a -> value1 a -> CodeGenFunction r (CmpValueResult value0 value1 a)Source

Compare floating point values.

select :: CmpRet a => Value (CmpResult a) -> Value a -> Value a -> CodeGenFunction r (Value a)Source

Select between two values depending on a boolean.

Fast math

Other

phi :: forall a r. IsFirstClass a => [(Value a, BasicBlock)] -> CodeGenFunction r (Value a)Source

Join several variables (virtual registers) from different basic blocks into one. All of the variables in the list are joined. See also addPhiInputs.

addPhiInputsSource

Arguments

:: forall a r . IsFirstClass a 
=> Value a

Must be a variable from a call to phi.

-> [(Value a, BasicBlock)]

Variables to add.

-> CodeGenFunction r () 

Add additional inputs to an existing phi node. The reason for this instruction is that sometimes the structure of the code makes it impossible to have all variables in scope at the point where you need the phi node.

call :: CallArgs f g r => Function f -> gSource

Call a function with the given arguments. The call instruction is variadic, i.e., the number of arguments it takes depends on the type of f.

callWithConv :: CallArgs f g r => CallingConvention -> Function f -> gSource

Call a function with the given arguments. The call instruction is variadic, i.e., the number of arguments it takes depends on the type of f. This also sets the calling convention of the call to the function. As LLVM itself defines, if the calling conventions of the calling instruction and the function being called are different, undefined behavior results.

data Call a Source

applyCall :: Call (a -> b) -> Value a -> Call bSource

Classes and types

class (ValueCons value0, ValueCons value1) => ValueCons2 value0 value1 Source

Associated Types

type BinOpValue value0 value1 :: * -> *Source

class Ret a r Source

Acceptable arguments to the ret instruction.

Instances

Ret () () 
Ret (Value a) a 

class (f ~ CalledFunction g, r ~ CallerResult g, g ~ CallerFunction f r) => CallArgs f g r Source

Acceptable arguments to call.

Instances

CallArgs (IO a) (CodeGenFunction r (Value a)) r 
CallArgs b b' r => CallArgs (a -> b) (Value a -> b') r 

class IsFunction f => FunctionArgs f Source

Associated Types

type FunctionCodeGen f :: *Source

type FunctionResult f :: *Source

Instances

class AllocArg a Source

Acceptable argument to array memory allocation.

class GetElementPtr optr ixs Source

Acceptable arguments to getElementPointer.

Associated Types

type ElementPtrType optr ixs :: *Source

Instances

class IsIndexArg a Source

Acceptable single index to getElementPointer.

class IsPrimitive i => IsIndexType i Source

In principle we do not need the getValueArg method, because we could just use unValue. However, we want to prevent users from defining their own (disfunctional) IsIndexType instances.

class GetValue agg ix Source

Acceptable arguments to extractvalue and insertvalue.

Associated Types

type ValueType agg ix :: *Source

Instances

(GetField as i, Natural i) => GetValue (Struct as) (Proxy i) 
(IsFirstClass a, Natural n) => GetValue (Array n a) Word64 
(IsFirstClass a, Natural n) => GetValue (Array n a) Word32 
(IsFirstClass a, Natural n, Natural i, :<: i n) => GetValue (Array n a) (Proxy i) 

class GetField as i Source

Associated Types

type FieldType as i :: *Source

Instances

GetField (a, as) Zero 
GetField as (Pred (Pos i0 i1)) => GetField (a, as) (Pos i0 i1) 

Types classification

Type classifier

class IsType a whereSource

The IsType class classifies all types that have an LLVM representation.

Special type classifiers

class Integer n => Natural n

Instances

Natural Zero 
(Pos x, Digits xs) => Natural (Pos x xs) 

class Natural n => Positive n

Instances

(Pos x, Digits xs) => Positive (Pos x xs) 

class IsType a => IsFunction a Source

Function type.

Instances

Others

data VectorShape n Source

Instances

class Shape shape Source

Associated Types

type ShapedType shape a :: *Source

class StructFields as Source

Instances

Structs

class CurryStruct f whereSource

Associated Types

type UncurriedArgument f Source

type UncurriedResult f Source

Instances

class UncurryStruct a whereSource

Associated Types

type Curried a b Source

Methods

uncurryStruct :: Curried a b -> Struct a -> bSource

Instances

type :& a as = (a, as)Source

(&) :: a -> as -> a :& asSource

Type tests

data VarArgs a Source

The VarArgs type is a placeholder for the real IO type that can be obtained with castVarArgs.

class CastVarArgs a b Source

Define what vararg types are permissible.

Instances

CastVarArgs (VarArgs a) (IO a) 
(IsFirstClass a, CastVarArgs (VarArgs b) c) => CastVarArgs (VarArgs b) (a -> c) 
CastVarArgs b c => CastVarArgs (a -> b) (a -> c) 

Extra types

newtype IntN n Source

Variable sized signed integer. The n parameter should belong to PosI.

Constructors

IntN Integer 

newtype WordN n Source

Variable sized unsigned integer. The n parameter should belong to PosI.

Constructors

WordN Integer 

newtype Array n a Source

Fixed sized arrays, the array size is encoded in the n parameter.

Constructors

Array [a] 

Instances

Typeable2 Array 
Show a => Show (Array n a) 
(Natural n, IsSized a, Natural (:*: n (SizeOf a))) => IsSized (Array n a) 
(Natural n, IsSized a) => IsFirstClass (Array n a) 
(Natural n, IsSized a) => IsType (Array n a) 
(IsConst a, IsSized a, Natural n) => IsConst (Array n a) 
(Natural n, Marshal a, IsSized a) => Marshal (Array n a) 
(IsFirstClass a, Natural n) => GetValue (Array n a) Word64 
(IsFirstClass a, Natural n) => GetValue (Array n a) Word32 
(IsFirstClass a, Natural n, Natural i, :<: i n) => GetValue (Array n a) (Proxy i) 
(GetElementPtr o i, IsIndexArg a, Natural k) => GetElementPtr (Array k o) (a, i) 

newtype Vector n a Source

Fixed sized vector, the array size is encoded in the n parameter.

Constructors

Vector (FixedList (ToUnary n) a) 

Instances

Positive n => Functor (Vector n) 
Positive n => Applicative (Vector n) 
Positive n => Foldable (Vector n) 
Positive n => Traversable (Vector n) 
(Enum a, Positive n) => Enum (Vector n a) 
(Eq a, Positive n) => Eq (Vector n a) 
(Floating a, Positive n) => Floating (Vector n a) 
(Fractional a, Positive n) => Fractional (Vector n a) 
(Integral a, Positive n) => Integral (Vector n a) 
(Num a, Positive n) => Num (Vector n a) 
(Ord a, Positive n) => Ord (Vector n a) 
(Real a, Positive n) => Real (Vector n a) 
(RealFloat a, Positive n) => RealFloat (Vector n a) 
(RealFrac a, Positive n) => RealFrac (Vector n a) 
(Natural n, Show a) => Show (Vector n a) 
(Positive n, Arbitrary a) => Arbitrary (Vector n a) 
(Storable a, Positive n, IsPrimitive a) => Storable (Vector n a) 
(Positive n, IsPrimitive a, IsSized a, Natural (:*: n (SizeOf a))) => IsSized (Vector n a) 
(Positive n, IsPrimitive a) => IsFirstClass (Vector n a) 
(Positive n, IsPrimitive a) => IsScalarOrVector (Vector n a) 
(Positive n, IsPrimitive a, IsFloating a) => IsFloating (Vector n a) 
(Positive n, IsPrimitive a, IsInteger a) => IsIntegerOrPointer (Vector n a) 
(Positive n, IsPrimitive a, IsInteger a) => IsInteger (Vector n a) 
(Positive n, IsPrimitive a, IsArithmetic a) => IsArithmetic (Vector n a) 
(Positive n, IsPrimitive a) => IsType (Vector n a) 
(IsPrimitive a, IsConst a, Positive n) => IsConst (Vector n a) 
(Positive n, Marshal a, IsPrimitive a) => Marshal (Vector n a) 
(CmpRet a, IsPrimitive a, Positive n) => CmpRet (Vector n a) 
(Positive n, IsPrimitive a, CallIntrinsic a) => CallIntrinsic (Vector n a) 
(GetElementPtr o i, IsIndexArg a, Positive k) => GetElementPtr (Vector k o) (a, i) 

data Label Source

Label type, produced by a basic block.

newtype Struct a Source

Struct types; a list (nested tuple) of component types.

Constructors

Struct a 

Values and constants

valueOf :: IsConst a => a -> Value aSource

zero :: forall a. IsType a => ConstValue aSource

allOnes :: forall a. IsInteger a => ConstValue aSource

undef :: forall a. IsType a => ConstValue aSource

class IsConstFields a Source

Instances

constVector :: forall a n u. (Positive n, ToUnary n ~ u, Length (FixedList u) ~ u) => FixedList u (ConstValue a) -> ConstValue (Vector n a)Source

Make a constant vector.

constArray :: forall a n. (IsSized a, Natural n) => [ConstValue a] -> ConstValue (Array n a)Source

constCyclicVector :: forall a n. Positive n => T [] (ConstValue a) -> ConstValue (Vector n a)Source

Make a constant vector. Replicates or truncates the list to get length n.

constCyclicArray :: forall a n. (IsSized a, Natural n) => T [] (ConstValue a) -> ConstValue (Vector n a)Source

Make a constant array. Replicates or truncates the list to get length n.

constStruct :: IsConstStruct c => c -> ConstValue (Struct (ConstStructOf c))Source

Make a constant struct.

constPackedStruct :: IsConstStruct c => c -> ConstValue (PackedStruct (ConstStructOf c))Source

Make a constant packed struct.

toVector :: MkVector n a => Tuple n a -> Vector n aSource

fromVector :: MkVector n a => Vector n a -> Tuple n aSource

cyclicVector :: Positive n => T [] a -> Vector n aSource

Make a constant vector. Replicates or truncates the list to get length n. This behaviour is consistent uncurry that of constCyclicVector. May be abused for constructing vectors from lists uncurry statically unknown size.

Code generation

Functions

type Function a = Value (FunPtr a)Source

A function is simply a pointer to the function.

newFunction :: forall a. IsFunction a => Linkage -> CodeGenModule (Function a)Source

Create a new function. Use newNamedFunction to create a function with external linkage, since it needs a known name.

newNamedFunctionSource

Arguments

:: forall a . IsFunction a 
=> Linkage 
-> String

Function name

-> CodeGenModule (Function a) 

Create a new named function.

defineFunctionSource

Arguments

:: forall f . FunctionArgs f 
=> Function f

Function to define (created by newFunction).

-> FunctionCodeGen f

Function body.

-> CodeGenModule () 

Define a function body. The basic block returned by the function is the function entry point.

createFunctionSource

Arguments

:: FunctionArgs f 
=> Linkage 
-> FunctionCodeGen f

Function body.

-> CodeGenModule (Function f) 

Create a new function with the given body.

createNamedFunctionSource

Arguments

:: FunctionArgs f 
=> Linkage 
-> String 
-> FunctionCodeGen f

Function body.

-> CodeGenModule (Function f) 

Create a new function with the given body.

setFuncCallConv :: Function a -> CallingConvention -> CodeGenModule ()Source

Set the calling convention of a function. By default it is the C calling convention.

liftCodeGenModule :: CodeGenModule a -> CodeGenFunction r aSource

Allows you to define part of a module while in the middle of defining a function.

getParams :: Value -> IO [(String, Value)]Source

Global variable creation

type Global a = Value (Ptr a)Source

newGlobal :: forall a. IsType a => Bool -> Linkage -> TGlobal aSource

Create a new global variable.

newNamedGlobalSource

Arguments

:: forall a . IsType a 
=> Bool

Constant?

-> Linkage

Visibility

-> String

Name

-> TGlobal a 

Create a new named global variable.

defineGlobal :: Global a -> ConstValue a -> CodeGenModule ()Source

Give a global variable a (constant) value.

createGlobal :: IsType a => Bool -> Linkage -> ConstValue a -> TGlobal aSource

Create and define a global variable.

createNamedGlobal :: IsType a => Bool -> Linkage -> String -> ConstValue a -> TGlobal aSource

Create and define a named global variable.

externFunction :: forall a r. IsFunction a => String -> CodeGenFunction r (Function a)Source

Create a reference to an external function while code generating for a function. If LLVM cannot resolve its name, then you may try staticFunction.

staticFunction :: forall f r. IsFunction f => FunPtr f -> CodeGenFunction r (Function f)Source

Make an external C function with a fixed address callable from LLVM code. This callback function can also be a Haskell function, that was imported like

 foreign import ccall "&nextElement"
    nextElementFunPtr :: FunPtr (StablePtr (IORef [Word32]) -> IO Word32)

See examples/List.hs.

When you only use externFunction, then LLVM cannot resolve the name. (However, I do not know why.) Thus staticFunction manages a list of static functions. This list is automatically installed by simpleFunction and can be manually obtained by getGlobalMappings and installed by addGlobalMappings. "Installing" means calling LLVM's addGlobalMapping according to http://old.nabble.com/jit-with-external-functions-td7769793.html.

staticNamedFunction :: forall f r. IsFunction f => String -> FunPtr f -> CodeGenFunction r (Function f)Source

Due to https://llvm.org/bugs/show_bug.cgi?id=20656 this will fail with MCJIT of LLVM-3.6.

externGlobal :: forall a r. IsType a => Bool -> String -> CodeGenFunction r (Global a)Source

As externFunction, but for Globals rather than Functions

staticGlobal :: forall a r. IsType a => Bool -> Ptr a -> CodeGenFunction r (Global a)Source

As staticFunction, but for Globals rather than Functions

getGlobalMappings :: CodeGenModule GlobalMappingsSource

Get a list created by calls to staticFunction that must be passed to the execution engine via addGlobalMappings.

Globals

data Linkage

An enumeration for the kinds of linkage for global values.

Constructors

ExternalLinkage

Externally visible function

AvailableExternallyLinkage 
LinkOnceAnyLinkage

Keep one copy of function when linking (inline)

LinkOnceODRLinkage

Same, but only replaced by something equivalent.

LinkOnceODRAutoHideLinkage

Like LinkOnceODR, but possibly hidden.

WeakAnyLinkage

Keep one copy of named function when linking (weak)

WeakODRLinkage

Same, but only replaced by something equivalent.

AppendingLinkage

Special purpose, only applies to global arrays

InternalLinkage

Rename collisions when linking (static functions)

PrivateLinkage

Like Internal, but omit from symbol table

DLLImportLinkage

Function to be imported from DLL

DLLExportLinkage

Function to be accessible from DLL

ExternalWeakLinkage

ExternalWeak linkage description

GhostLinkage

Stand-in functions for streaming fns from BC files

CommonLinkage

Tentative definitions

LinkerPrivateLinkage

Like Private, but linker removes.

LinkerPrivateWeakLinkage

Like LinkerPrivate, but is weak.

Basic blocks

data BasicBlock Source

A basic block is a sequence of non-branching instructions, terminated by a control flow instruction.

getBasicBlocks :: Value -> IO [(String, BasicBlock)]Source

getInstructions :: BasicBlock -> IO [(String, Value)]Source

getOperands :: Value -> IO [(String, Value)]Source

hasUsers :: Value -> IO BoolSource

getUsers :: [Use] -> IO [(String, Value)]Source

getUses :: Value -> IO [Use]Source

getUser :: Use -> IO ValueSource

isChildOf :: BasicBlock -> Value -> IO BoolSource

Misc

addAttributes :: Value a -> AttributeIndex -> [Attribute] -> CodeGenFunction r ()Source

Add attributes to a value. Beware, what attributes are allowed depends on what kind of value it is.

newtype AttributeIndex

Constructors

AttributeIndex Word32 

castVarArgs :: CastVarArgs a b => Function a -> Function bSource

Convert a varargs function to a regular function.

Debugging

dumpValue :: Value a -> IO ()Source

Print a value.

dumpType :: Value a -> IO ()Source

Print a type.

getValueName :: Value a -> IO StringSource

Get the name of a Value.

annotateValueList :: [Value] -> IO [(String, Value)]Source