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

Safe HaskellNone
LanguageHaskell98

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.

Instances

newModule :: IO Module Source #

Create a new module.

newNamedModule Source #

Arguments

:: String

module name

-> IO Module 

Create a new explicitely named module.

defineModule Source #

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.

createModule Source #

Arguments

:: CodeGenModule a

module body

-> IO a 

Create a new module with the given body.

data ModuleProvider Source #

A module provider is used by the code generator to get access to a module.

createModuleProviderForExistingModule :: Module -> IO ModuleProvider Source #

Turn a module into a module provider.

data PassManager Source #

Manage compile passes.

createPassManager :: IO PassManager Source #

Create a pass manager.

createFunctionPassManager :: ModuleProvider -> IO PassManager Source #

Create a pass manager for a module.

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

Write a module to a file.

readBitcodeFromFile :: String -> IO Module Source #

Read a module from a file.

getFunctions :: Module -> IO [(String, Value)] Source #

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 Terminate Source #

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

condBr Source #

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.

br Source #

Arguments

:: BasicBlock

Branch target.

-> CodeGenFunction r Terminate 

Unconditionally branch to the given basic block.

switch Source #

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.

invoke Source #

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.

invokeWithConv Source #

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.

invokeFromFunction Source #

Arguments

:: BasicBlock

Normal return point.

-> BasicBlock

Exception return point.

-> Function f

Function to call.

-> Call f 

invokeWithConvFromFunction Source #

Arguments

:: CallingConvention

Calling convention

-> BasicBlock

Normal return point.

-> BasicBlock

Exception return point.

-> Function f

Function to call.

-> Call f 

unreachable :: CodeGenFunction r Terminate Source #

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

Arithmetic binary operations

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

add :: (IsArithmetic c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

sub :: (IsArithmetic c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

mul :: (IsArithmetic c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

neg :: (IsArithmetic b, AUnOp a, a ~ v b) => a -> CodeGenFunction r a Source #

iadd :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

isub :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

imul :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

ineg :: (IsInteger b, AUnOp a, a ~ v b) => a -> CodeGenFunction r a Source #

fadd :: (IsFloating c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

fsub :: (IsFloating c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

fmul :: (IsFloating c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

fneg :: (IsFloating b, AUnOp a, a ~ v b) => a -> CodeGenFunction r a Source #

idiv :: forall a b c r v. (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

signed or unsigned integer division depending on the type

irem :: forall a b c r v. (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

signed or unsigned remainder depending on the type

udiv :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

Deprecated: use idiv instead

sdiv :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

Deprecated: use idiv instead

fdiv :: (IsFloating c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

Floating point division.

urem :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

Deprecated: use irem instead

srem :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

Deprecated: use irem instead

frem :: (IsFloating c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

Floating point remainder.

Logical binary operations

Logical instructions with the normal semantics.

shl :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

lshr :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

ashr :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

and :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

or :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

xor :: (IsInteger c, ABinOp a b, v c ~ ABinOpResult a b) => a -> b -> CodeGenFunction r (v c) Source #

inv :: (IsInteger b, AUnOp a, a ~ v b) => a -> CodeGenFunction r a Source #

Vector operations

extractelement Source #

Arguments

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

Vector

-> Value Word32

Index into the vector

-> CodeGenFunction r (Value a) 

Get a value from a vector.

insertelement Source #

Arguments

:: Positive n 
=> 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) => Value (Vector n a) -> Value (Vector n a) -> ConstValue (Vector m Word32) -> CodeGenFunction r (Value (Vector m a)) Source #

Permute vector.

Aggregate operation

extractvalue Source #

Arguments

:: GetValue agg i 
=> Value agg

Aggregate

-> i

Index into the aggregate

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

Get a value from an aggregate.

insertvalue Source #

Arguments

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

load Source #

Arguments

:: Value (Ptr a)

Address to load from.

-> CodeGenFunction r (Value a) 

Load a value from memory.

store Source #

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 :: (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements 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 :: (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements 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 :: (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements 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 a b r. (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements 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 a b r. (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b) Source #

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

sadapt :: forall a b r. (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements b) => Value a -> CodeGenFunction r (Value b) Source #

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

adapt :: forall a b r. (IsInteger a, IsInteger b, NumberOfElements a ~ NumberOfElements b, Signed a ~ Signed b) => Value a -> CodeGenFunction r (Value b) Source #

It is sadapt or zadapt depending on the sign mode.

fptrunc :: (IsFloating a, IsFloating b, NumberOfElements a ~ NumberOfElements b, IsSized a, IsSized b, SizeOf a :>: SizeOf b) => Value a -> CodeGenFunction r (Value b) Source #

Truncate a floating point value.

fpext :: (IsFloating a, IsFloating b, NumberOfElements a ~ NumberOfElements b, IsSized a, IsSized b, SizeOf a :<: SizeOf b) => Value a -> CodeGenFunction r (Value b) Source #

Extend a floating point value.

fptoui :: (IsFloating a, IsInteger b, NumberOfElements a ~ NumberOfElements 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 :: (IsFloating a, IsInteger b, NumberOfElements a ~ NumberOfElements 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 r a b. (IsFloating a, IsInteger b, NumberOfElements a ~ NumberOfElements 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 :: (IsInteger a, IsFloating b, NumberOfElements a ~ NumberOfElements 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 :: (IsInteger a, IsFloating b, NumberOfElements a ~ NumberOfElements 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 r a b. (IsInteger a, IsFloating b, NumberOfElements a ~ NumberOfElements 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 :: (IsInteger b, IsPrimitive b) => Value (Ptr a) -> CodeGenFunction r (Value b) Source #

Convert a pointer to an integer.

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

Convert an integer to a pointer.

bitcast :: (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.

bitcastElements :: (Positive n, IsPrimitive a, IsPrimitive b, IsSized a, IsSized b, SizeOf a ~ SizeOf b) => Value (Vector n a) -> CodeGenFunction r (Value (Vector n b)) Source #

Like bitcast for vectors but it enforces that the number of elements remains the same.

Comparison

data FPPredicate Source #

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

FPT

Always true (always folded)

class CmpRet (CmpType a b) => CmpOp a b Source #

Acceptable operands to comparison instructions.

Minimal complete definition

cmpop

Instances

CmpRet a => CmpOp (ConstValue a) (ConstValue a) Source # 

Associated Types

type CmpType (ConstValue a) (ConstValue a) :: *

type CmpValue (ConstValue a) (ConstValue a) :: * -> *

Methods

cmpop :: FFIConstBinOp -> FFIBinOp -> ConstValue a -> ConstValue a -> CodeGenFunction r (CmpValueResult (ConstValue a) (ConstValue a))

CmpRet a => CmpOp (ConstValue a) (Value a) Source # 

Associated Types

type CmpType (ConstValue a) (Value a) :: *

type CmpValue (ConstValue a) (Value a) :: * -> *

Methods

cmpop :: FFIConstBinOp -> FFIBinOp -> ConstValue a -> Value a -> CodeGenFunction r (CmpValueResult (ConstValue a) (Value a))

CmpRet a => CmpOp (Value a) (ConstValue a) Source # 

Associated Types

type CmpType (Value a) (ConstValue a) :: *

type CmpValue (Value a) (ConstValue a) :: * -> *

Methods

cmpop :: FFIConstBinOp -> FFIBinOp -> Value a -> ConstValue a -> CodeGenFunction r (CmpValueResult (Value a) (ConstValue a))

CmpRet a => CmpOp (Value a) (Value a) Source # 

Associated Types

type CmpType (Value a) (Value a) :: *

type CmpValue (Value a) (Value a) :: * -> *

Methods

cmpop :: FFIConstBinOp -> FFIBinOp -> Value a -> Value a -> CodeGenFunction r (CmpValueResult (Value a) (Value a))

class CmpRet c Source #

Minimal complete definition

cmpBld, cmpCnst

Associated Types

type CmpResult c :: * Source #

Instances

CmpRet Bool Source # 

Associated Types

type CmpResult Bool :: * Source #

Methods

cmpBld :: Proxy Bool -> CmpPredicate -> FFIBinOp

cmpCnst :: Proxy Bool -> CmpPredicate -> FFIConstBinOp

CmpRet Double Source # 

Associated Types

type CmpResult Double :: * Source #

Methods

cmpBld :: Proxy Double -> CmpPredicate -> FFIBinOp

cmpCnst :: Proxy Double -> CmpPredicate -> FFIConstBinOp

CmpRet Float Source # 

Associated Types

type CmpResult Float :: * Source #

Methods

cmpBld :: Proxy Float -> CmpPredicate -> FFIBinOp

cmpCnst :: Proxy Float -> CmpPredicate -> FFIConstBinOp

CmpRet Int8 Source # 

Associated Types

type CmpResult Int8 :: * Source #

Methods

cmpBld :: Proxy Int8 -> CmpPredicate -> FFIBinOp

cmpCnst :: Proxy Int8 -> CmpPredicate -> FFIConstBinOp

CmpRet Int16 Source # 

Associated Types

type CmpResult Int16 :: * Source #

Methods

cmpBld :: Proxy Int16 -> CmpPredicate -> FFIBinOp

cmpCnst :: Proxy Int16 -> CmpPredicate -> FFIConstBinOp

CmpRet Int32 Source # 

Associated Types

type CmpResult Int32 :: * Source #

Methods

cmpBld :: Proxy Int32 -> CmpPredicate -> FFIBinOp

cmpCnst :: Proxy Int32 -> CmpPredicate -> FFIConstBinOp

CmpRet Int64 Source # 

Associated Types

type CmpResult Int64 :: * Source #

Methods

cmpBld :: Proxy Int64 -> CmpPredicate -> FFIBinOp

cmpCnst :: Proxy Int64 -> CmpPredicate -> FFIConstBinOp

CmpRet Word8 Source # 

Associated Types

type CmpResult Word8 :: * Source #

Methods

cmpBld :: Proxy Word8 -> CmpPredicate -> FFIBinOp

cmpCnst :: Proxy Word8 -> CmpPredicate -> FFIConstBinOp

CmpRet Word16 Source # 

Associated Types

type CmpResult Word16 :: * Source #

Methods

cmpBld :: Proxy Word16 -> CmpPredicate -> FFIBinOp

cmpCnst :: Proxy Word16 -> CmpPredicate -> FFIConstBinOp

CmpRet Word32 Source # 

Associated Types

type CmpResult Word32 :: * Source #

Methods

cmpBld :: Proxy Word32 -> CmpPredicate -> FFIBinOp

cmpCnst :: Proxy Word32 -> CmpPredicate -> FFIConstBinOp

CmpRet Word64 Source # 

Associated Types

type CmpResult Word64 :: * Source #

Methods

cmpBld :: Proxy Word64 -> CmpPredicate -> FFIBinOp

cmpCnst :: Proxy Word64 -> CmpPredicate -> FFIConstBinOp

CmpRet FP128 Source # 

Associated Types

type CmpResult FP128 :: * Source #

Methods

cmpBld :: Proxy FP128 -> CmpPredicate -> FFIBinOp

cmpCnst :: Proxy FP128 -> CmpPredicate -> FFIConstBinOp

CmpRet (Ptr a) Source # 

Associated Types

type CmpResult (Ptr a) :: * Source #

Methods

cmpBld :: Proxy (Ptr a) -> CmpPredicate -> FFIBinOp

cmpCnst :: Proxy (Ptr a) -> CmpPredicate -> FFIConstBinOp

(CmpRet a, IsPrimitive a, Positive n) => CmpRet (Vector n a) Source # 

Associated Types

type CmpResult (Vector n a) :: * Source #

Methods

cmpBld :: Proxy (Vector n a) -> CmpPredicate -> FFIBinOp

cmpCnst :: Proxy (Vector n a) -> CmpPredicate -> FFIConstBinOp

type CmpValueResult a b = CmpValue a b (CmpResult (CmpType a b)) Source #

cmp :: forall a b r. CmpOp a b => CmpPredicate -> a -> b -> CodeGenFunction r (CmpValueResult a b) 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 :: (CmpOp a b, Ptr c ~ CmpType a b) => IntPredicate -> a -> b -> CodeGenFunction r (CmpValueResult a b) Source #

icmp :: (IsIntegerOrPointer c, CmpOp a b, c ~ CmpType a b) => IntPredicate -> a -> b -> CodeGenFunction r (CmpValueResult a b) Source #

Deprecated: use cmp or pcmp instead

Compare integers.

fcmp :: (IsFloating c, CmpOp a b, c ~ CmpType a b) => FPPredicate -> a -> b -> CodeGenFunction r (CmpValueResult a b) Source #

Compare floating point values.

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

Select between two values depending on a boolean.

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.

addPhiInputs Source #

Arguments

:: 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 -> g Source #

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 -> g Source #

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 b infixl 4 Source #

Classes and types

type Terminate = () Source #

class Ret a r Source #

Acceptable arguments to the ret instruction.

Minimal complete definition

ret'

Instances

Ret () () Source # 

Methods

ret' :: () -> CodeGenFunction () Terminate

Ret (Value a) a Source # 

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

Acceptable arguments to call.

Minimal complete definition

doCall

Instances

CallArgs (IO a) (CodeGenFunction r (Value a)) r Source # 

Associated Types

type CalledFunction (CodeGenFunction r (Value a)) :: *

type CallerResult (CodeGenFunction r (Value a)) :: *

type CallerFunction (IO a) r :: *

Methods

doCall :: Call (IO a) -> CodeGenFunction r (Value a)

CallArgs b b' r => CallArgs (a -> b) (Value a -> b') r Source # 

Associated Types

type CalledFunction (Value a -> b') :: *

type CallerResult (Value a -> b') :: *

type CallerFunction (a -> b) r :: *

Methods

doCall :: Call (a -> b) -> Value a -> b'

class AUnOp a Source #

Acceptable arguments to arithmetic unary instructions.

Minimal complete definition

aunop

Instances

AUnOp (ConstValue a) Source # 

Methods

aunop :: FFIConstUnOp -> FFIUnOp -> ConstValue a -> CodeGenFunction r (ConstValue a)

AUnOp (Value a) Source # 

Methods

aunop :: FFIConstUnOp -> FFIUnOp -> Value a -> CodeGenFunction r (Value a)

class ABinOp a b Source #

Acceptable arguments to arithmetic binary instructions.

Minimal complete definition

abinop

Associated Types

type ABinOpResult a b :: * Source #

Instances

ABinOp (ConstValue a) (ConstValue a) Source # 

Associated Types

type ABinOpResult (ConstValue a) (ConstValue a) :: * Source #

Methods

abinop :: FFIConstBinOp -> FFIBinOp -> ConstValue a -> ConstValue a -> CodeGenFunction r (ABinOpResult (ConstValue a) (ConstValue a))

ABinOp (ConstValue a) (Value a) Source # 

Associated Types

type ABinOpResult (ConstValue a) (Value a) :: * Source #

Methods

abinop :: FFIConstBinOp -> FFIBinOp -> ConstValue a -> Value a -> CodeGenFunction r (ABinOpResult (ConstValue a) (Value a))

ABinOp (Value a) (ConstValue a) Source # 

Associated Types

type ABinOpResult (Value a) (ConstValue a) :: * Source #

Methods

abinop :: FFIConstBinOp -> FFIBinOp -> Value a -> ConstValue a -> CodeGenFunction r (ABinOpResult (Value a) (ConstValue a))

ABinOp (Value a) (Value a) Source # 

Associated Types

type ABinOpResult (Value a) (Value a) :: * Source #

Methods

abinop :: FFIConstBinOp -> FFIBinOp -> Value a -> Value a -> CodeGenFunction r (ABinOpResult (Value a) (Value a))

class IsConst a Source #

Minimal complete definition

constOf

Instances

IsConst Bool Source # 
IsConst Double Source # 
IsConst Float Source # 
IsConst Int8 Source # 
IsConst Int16 Source # 
IsConst Int32 Source # 
IsConst Int64 Source # 
IsConst Word8 Source # 
IsConst Word16 Source # 
IsConst Word32 Source # 
IsConst Word64 Source # 
IsConst (StablePtr a) Source # 
IsType a => IsConst (Ptr a) Source # 

Methods

constOf :: Ptr a -> ConstValue (Ptr a) Source #

IsFunction a => IsConst (FunPtr a) Source # 

Methods

constOf :: FunPtr a -> ConstValue (FunPtr a) Source #

IsConstFields a => IsConst (PackedStruct a) Source # 
IsConstFields a => IsConst (Struct a) Source # 

Methods

constOf :: Struct a -> ConstValue (Struct a) Source #

(IsPrimitive a, IsConst a, Positive n) => IsConst (Vector n a) Source # 

Methods

constOf :: Vector n a -> ConstValue (Vector n a) Source #

(IsConst a, IsSized a, Natural n) => IsConst (Array n a) Source # 

Methods

constOf :: Array n a -> ConstValue (Array n a) Source #

class IsFunction f => FunctionArgs f Source #

Minimal complete definition

paramFunc

Associated Types

type FunctionCodeGen f :: * Source #

type FunctionResult f :: * Source #

Instances

IsFirstClass a => FunctionArgs (IO a) Source # 

Associated Types

type FunctionCodeGen (IO a) :: * Source #

type FunctionResult (IO a) :: * Source #

Methods

paramFunc :: FunctionCodeGen (IO a) -> Parameterized (FunctionResult (IO a)) (IO a)

(FunctionArgs b, IsFirstClass a) => FunctionArgs (a -> b) Source # 

Associated Types

type FunctionCodeGen (a -> b) :: * Source #

type FunctionResult (a -> b) :: * Source #

Methods

paramFunc :: FunctionCodeGen (a -> b) -> Parameterized (FunctionResult (a -> b)) (a -> b)

class AllocArg a Source #

Acceptable argument to array memory allocation.

Minimal complete definition

getAllocArg

class GetElementPtr optr ixs Source #

Acceptable arguments to getElementPointer.

Minimal complete definition

getIxList

Associated Types

type ElementPtrType optr ixs :: * Source #

Instances

GetElementPtr a () Source # 

Associated Types

type ElementPtrType a () :: * Source #

Methods

getIxList :: Proxy a -> () -> [ValueRef]

(GetElementPtr (FieldType fs a) i, Natural a) => GetElementPtr (PackedStruct fs) (Proxy a, i) Source # 

Associated Types

type ElementPtrType (PackedStruct fs) (Proxy a, i) :: * Source #

Methods

getIxList :: Proxy (PackedStruct fs) -> (Proxy a, i) -> [ValueRef]

(GetElementPtr (FieldType fs a) i, Natural a) => GetElementPtr (Struct fs) (Proxy a, i) Source # 

Associated Types

type ElementPtrType (Struct fs) (Proxy a, i) :: * Source #

Methods

getIxList :: Proxy (Struct fs) -> (Proxy a, i) -> [ValueRef]

(GetElementPtr o i, IsIndexArg a, Positive k) => GetElementPtr (Vector k o) (a, i) Source # 

Associated Types

type ElementPtrType (Vector k o) (a, i) :: * Source #

Methods

getIxList :: Proxy (Vector k o) -> (a, i) -> [ValueRef]

(GetElementPtr o i, IsIndexArg a, Natural k) => GetElementPtr (Array k o) (a, i) Source # 

Associated Types

type ElementPtrType (Array k o) (a, i) :: * Source #

Methods

getIxList :: Proxy (Array k o) -> (a, i) -> [ValueRef]

class GetValue agg ix Source #

Acceptable arguments to extractvalue and insertvalue.

Minimal complete definition

getIx

Associated Types

type ValueType agg ix :: * Source #

Instances

(GetField as i, Natural i) => GetValue (Struct as) (Proxy i) Source # 

Associated Types

type ValueType (Struct as) (Proxy i) :: * Source #

Methods

getIx :: Proxy (Struct as) -> Proxy i -> CUInt

(IsFirstClass a, Natural n) => GetValue (Array n a) Word64 Source # 

Associated Types

type ValueType (Array n a) Word64 :: * Source #

Methods

getIx :: Proxy (Array n a) -> Word64 -> CUInt

(IsFirstClass a, Natural n) => GetValue (Array n a) Word32 Source # 

Associated Types

type ValueType (Array n a) Word32 :: * Source #

Methods

getIx :: Proxy (Array n a) -> Word32 -> CUInt

(IsFirstClass a, Natural n, Natural i, (:<:) i n) => GetValue (Array n a) (Proxy i) Source # 

Associated Types

type ValueType (Array n a) (Proxy i) :: * Source #

Methods

getIx :: Proxy (Array n a) -> Proxy i -> CUInt

class GetField as i Source #

Associated Types

type FieldType as i :: * Source #

Instances

GetField (a, as) Zero Source # 

Associated Types

type FieldType (a, as) Zero :: * Source #

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

Associated Types

type FieldType (a, as) (Pos i0 i1) :: * Source #

Types classification

Type classifier

class IsType a where Source #

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

Minimal complete definition

typeDesc

Methods

typeDesc :: Proxy a -> TypeDesc Source #

Instances

IsType Bool Source # 
IsType Double Source # 
IsType Float Source # 
IsType Int8 Source # 
IsType Int16 Source # 
IsType Int32 Source # 
IsType Int64 Source # 
IsType Word8 Source # 
IsType Word16 Source # 
IsType Word32 Source # 
IsType Word64 Source # 
IsType () Source # 

Methods

typeDesc :: Proxy () -> TypeDesc Source #

IsType Label Source # 
IsType FP128 Source # 
IsType (StablePtr a) Source # 
IsFirstClass a => IsType (IO a) Source # 

Methods

typeDesc :: Proxy (IO a) -> TypeDesc Source #

IsType a => IsType (Ptr a) Source # 

Methods

typeDesc :: Proxy (Ptr a) -> TypeDesc Source #

IsFunction f => IsType (FunPtr f) Source # 
StructFields a => IsType (PackedStruct a) Source # 
StructFields a => IsType (Struct a) Source # 
Positive n => IsType (WordN n) Source # 

Methods

typeDesc :: Proxy (WordN n) -> TypeDesc Source #

Positive n => IsType (IntN n) Source # 

Methods

typeDesc :: Proxy (IntN n) -> TypeDesc Source #

IsType (VarArgs a) Source # 
(IsFirstClass a, IsFunction b) => IsType (a -> b) Source # 

Methods

typeDesc :: Proxy (a -> b) -> TypeDesc Source #

(Positive n, IsPrimitive a) => IsType (Vector n a) Source # 

Methods

typeDesc :: Proxy (Vector n a) -> TypeDesc Source #

(Natural n, IsSized a) => IsType (Array n a) Source # 

Methods

typeDesc :: Proxy (Array n a) -> TypeDesc Source #

Special type classifiers

class Integer n => Natural n #

Minimal complete definition

switchNat

Instances

Natural Zero 

Methods

switchNat :: f Zero -> (forall x xs. (Pos x, Digits xs) => f (Pos x xs)) -> f Zero #

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

Methods

switchNat :: f Zero -> (forall a xs0. (Pos a, Digits xs0) => f (Pos a xs0)) -> f (Pos x xs) #

class Natural n => Positive n #

Minimal complete definition

switchPos

Instances

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

Methods

switchPos :: (forall a xs0. (Pos a, Digits xs0) => f (Pos a xs0)) -> f (Pos x xs) #

class IsFirstClass a => IsArithmetic a where Source #

Arithmetic types, i.e., integral and floating types.

Minimal complete definition

arithmeticType

class (IsArithmetic a, IsIntegerOrPointer a) => IsInteger a Source #

Integral types.

Associated Types

type Signed a :: * Source #

Instances

IsInteger Bool Source # 

Associated Types

type Signed Bool :: * Source #

IsInteger Int8 Source # 

Associated Types

type Signed Int8 :: * Source #

IsInteger Int16 Source # 

Associated Types

type Signed Int16 :: * Source #

IsInteger Int32 Source # 

Associated Types

type Signed Int32 :: * Source #

IsInteger Int64 Source # 

Associated Types

type Signed Int64 :: * Source #

IsInteger Word8 Source # 

Associated Types

type Signed Word8 :: * Source #

IsInteger Word16 Source # 

Associated Types

type Signed Word16 :: * Source #

IsInteger Word32 Source # 

Associated Types

type Signed Word32 :: * Source #

IsInteger Word64 Source # 

Associated Types

type Signed Word64 :: * Source #

Positive n => IsInteger (WordN n) Source # 

Associated Types

type Signed (WordN n) :: * Source #

Positive n => IsInteger (IntN n) Source # 

Associated Types

type Signed (IntN n) :: * Source #

(Positive n, IsPrimitive a, IsInteger a) => IsInteger (Vector n a) Source # 

Associated Types

type Signed (Vector n a) :: * Source #

class (IsType a, Natural (SizeOf a)) => IsSized a Source #

Types with a fixed size.

Associated Types

type SizeOf a :: * Source #

Instances

IsSized Bool Source # 

Associated Types

type SizeOf Bool :: * Source #

IsSized Double Source # 

Associated Types

type SizeOf Double :: * Source #

IsSized Float Source # 

Associated Types

type SizeOf Float :: * Source #

IsSized Int8 Source # 

Associated Types

type SizeOf Int8 :: * Source #

IsSized Int16 Source # 

Associated Types

type SizeOf Int16 :: * Source #

IsSized Int32 Source # 

Associated Types

type SizeOf Int32 :: * Source #

IsSized Int64 Source # 

Associated Types

type SizeOf Int64 :: * Source #

IsSized Word8 Source # 

Associated Types

type SizeOf Word8 :: * Source #

IsSized Word16 Source # 

Associated Types

type SizeOf Word16 :: * Source #

IsSized Word32 Source # 

Associated Types

type SizeOf Word32 :: * Source #

IsSized Word64 Source # 

Associated Types

type SizeOf Word64 :: * Source #

IsSized FP128 Source # 

Associated Types

type SizeOf FP128 :: * Source #

IsSized (StablePtr a) Source # 

Associated Types

type SizeOf (StablePtr a) :: * Source #

IsType a => IsSized (Ptr a) Source # 

Associated Types

type SizeOf (Ptr a) :: * Source #

IsFunction a => IsSized (FunPtr a) Source # 

Associated Types

type SizeOf (FunPtr a) :: * Source #

StructFields as => IsSized (PackedStruct as) Source # 

Associated Types

type SizeOf (PackedStruct as) :: * Source #

StructFields as => IsSized (Struct as) Source # 

Associated Types

type SizeOf (Struct as) :: * Source #

Positive n => IsSized (WordN n) Source # 

Associated Types

type SizeOf (WordN n) :: * Source #

Positive n => IsSized (IntN n) Source # 

Associated Types

type SizeOf (IntN n) :: * Source #

(Positive n, IsPrimitive a, IsSized a, Natural ((:*:) n (SizeOf a))) => IsSized (Vector n a) Source # 

Associated Types

type SizeOf (Vector n a) :: * Source #

(Natural n, IsSized a, Natural ((:*:) n (SizeOf a))) => IsSized (Array n a) Source # 

Associated Types

type SizeOf (Array n a) :: * Source #

class IsType a => IsFunction a Source #

Function type.

Minimal complete definition

funcType

Instances

IsFirstClass a => IsFunction (IO a) Source # 

Methods

funcType :: [TypeDesc] -> Proxy (IO a) -> TypeDesc

IsFirstClass a => IsFunction (VarArgs a) Source # 

Methods

funcType :: [TypeDesc] -> Proxy (VarArgs a) -> TypeDesc

(IsFirstClass a, IsFunction b) => IsFunction (a -> b) Source # 

Methods

funcType :: [TypeDesc] -> Proxy (a -> b) -> TypeDesc

Others

class IsType a => IsScalarOrVector a Source #

Number of elements for instructions that handle both primitive and vector types

Associated Types

type NumberOfElements a :: * Source #

Instances

IsScalarOrVector Bool Source # 

Associated Types

type NumberOfElements Bool :: * Source #

IsScalarOrVector Double Source # 

Associated Types

type NumberOfElements Double :: * Source #

IsScalarOrVector Float Source # 

Associated Types

type NumberOfElements Float :: * Source #

IsScalarOrVector Int8 Source # 

Associated Types

type NumberOfElements Int8 :: * Source #

IsScalarOrVector Int16 Source # 

Associated Types

type NumberOfElements Int16 :: * Source #

IsScalarOrVector Int32 Source # 

Associated Types

type NumberOfElements Int32 :: * Source #

IsScalarOrVector Int64 Source # 

Associated Types

type NumberOfElements Int64 :: * Source #

IsScalarOrVector Word8 Source # 

Associated Types

type NumberOfElements Word8 :: * Source #

IsScalarOrVector Word16 Source # 

Associated Types

type NumberOfElements Word16 :: * Source #

IsScalarOrVector Word32 Source # 

Associated Types

type NumberOfElements Word32 :: * Source #

IsScalarOrVector Word64 Source # 

Associated Types

type NumberOfElements Word64 :: * Source #

IsScalarOrVector () Source # 

Associated Types

type NumberOfElements () :: * Source #

IsScalarOrVector Label Source # 

Associated Types

type NumberOfElements Label :: * Source #

IsScalarOrVector FP128 Source # 

Associated Types

type NumberOfElements FP128 :: * Source #

Positive n => IsScalarOrVector (WordN n) Source # 

Associated Types

type NumberOfElements (WordN n) :: * Source #

Positive n => IsScalarOrVector (IntN n) Source # 

Associated Types

type NumberOfElements (IntN n) :: * Source #

(Positive n, IsPrimitive a) => IsScalarOrVector (Vector n a) Source # 

Associated Types

type NumberOfElements (Vector n a) :: * Source #

class StructFields as Source #

Minimal complete definition

fieldTypes

Instances

StructFields () Source # 

Methods

fieldTypes :: Proxy () -> [TypeDesc]

(IsSized a, StructFields as) => StructFields ((:&) a as) Source # 

Methods

fieldTypes :: Proxy (a :& as) -> [TypeDesc]

Structs

type (:&) a as = (a, as) infixr 9 Source #

(&) :: a -> as -> a :& as infixr 9 Source #

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) Source # 
(IsFirstClass a, CastVarArgs (VarArgs b) c) => CastVarArgs (VarArgs b) (a -> c) Source # 
CastVarArgs b c => CastVarArgs (a -> b) (a -> c) Source # 

Extra types

newtype IntN n Source #

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

Constructors

IntN Integer 

Instances

Show (IntN n) Source # 

Methods

showsPrec :: Int -> IntN n -> ShowS #

show :: IntN n -> String #

showList :: [IntN n] -> ShowS #

Positive n => IsSized (IntN n) Source # 

Associated Types

type SizeOf (IntN n) :: * Source #

Positive n => IsFirstClass (IntN n) Source # 
Positive n => IsScalarOrVector (IntN n) Source # 

Associated Types

type NumberOfElements (IntN n) :: * Source #

Positive n => IsPrimitive (IntN n) Source # 
Positive n => IsIntegerOrPointer (IntN n) Source # 
Positive n => IsInteger (IntN n) Source # 

Associated Types

type Signed (IntN n) :: * Source #

Positive n => IsArithmetic (IntN n) Source # 
Positive n => IsType (IntN n) Source # 

Methods

typeDesc :: Proxy (IntN n) -> TypeDesc Source #

type SizeOf (IntN n) Source # 
type SizeOf (IntN n) = n
type NumberOfElements (IntN n) Source # 
type Signed (IntN n) Source # 
type Signed (IntN n) = True

newtype WordN n Source #

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

Constructors

WordN Integer 

Instances

Show (WordN n) Source # 

Methods

showsPrec :: Int -> WordN n -> ShowS #

show :: WordN n -> String #

showList :: [WordN n] -> ShowS #

Positive n => IsSized (WordN n) Source # 

Associated Types

type SizeOf (WordN n) :: * Source #

Positive n => IsFirstClass (WordN n) Source # 
Positive n => IsScalarOrVector (WordN n) Source # 

Associated Types

type NumberOfElements (WordN n) :: * Source #

Positive n => IsPrimitive (WordN n) Source # 
Positive n => IsIntegerOrPointer (WordN n) Source # 
Positive n => IsInteger (WordN n) Source # 

Associated Types

type Signed (WordN n) :: * Source #

Positive n => IsArithmetic (WordN n) Source # 
Positive n => IsType (WordN n) Source # 

Methods

typeDesc :: Proxy (WordN n) -> TypeDesc Source #

type SizeOf (WordN n) Source # 
type SizeOf (WordN n) = n
type NumberOfElements (WordN n) Source # 
type Signed (WordN n) Source # 
type Signed (WordN n) = False

newtype Array n a Source #

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

Constructors

Array [a] 

Instances

Show a => Show (Array n a) Source # 

Methods

showsPrec :: Int -> Array n a -> ShowS #

show :: Array n a -> String #

showList :: [Array n a] -> ShowS #

(Natural n, IsSized a, Natural ((:*:) n (SizeOf a))) => IsSized (Array n a) Source # 

Associated Types

type SizeOf (Array n a) :: * Source #

(Natural n, IsSized a) => IsFirstClass (Array n a) Source # 
(Natural n, IsSized a) => IsType (Array n a) Source # 

Methods

typeDesc :: Proxy (Array n a) -> TypeDesc Source #

(IsConst a, IsSized a, Natural n) => IsConst (Array n a) Source # 

Methods

constOf :: Array n a -> ConstValue (Array n a) Source #

(IsFirstClass a, Natural n) => GetValue (Array n a) Word64 Source # 

Associated Types

type ValueType (Array n a) Word64 :: * Source #

Methods

getIx :: Proxy (Array n a) -> Word64 -> CUInt

(IsFirstClass a, Natural n) => GetValue (Array n a) Word32 Source # 

Associated Types

type ValueType (Array n a) Word32 :: * Source #

Methods

getIx :: Proxy (Array n a) -> Word32 -> CUInt

(IsFirstClass a, Natural n, Natural i, (:<:) i n) => GetValue (Array n a) (Proxy i) Source # 

Associated Types

type ValueType (Array n a) (Proxy i) :: * Source #

Methods

getIx :: Proxy (Array n a) -> Proxy i -> CUInt

(GetElementPtr o i, IsIndexArg a, Natural k) => GetElementPtr (Array k o) (a, i) Source # 

Associated Types

type ElementPtrType (Array k o) (a, i) :: * Source #

Methods

getIxList :: Proxy (Array k o) -> (a, i) -> [ValueRef]

type SizeOf (Array n a) Source # 
type SizeOf (Array n a) = (:*:) n (SizeOf a)
type ValueType (Array n a) Word64 Source # 
type ValueType (Array n a) Word64 = a
type ValueType (Array n a) Word32 Source # 
type ValueType (Array n a) Word32 = a
type ValueType (Array n a) (Proxy i) Source # 
type ValueType (Array n a) (Proxy i) = a
type ElementPtrType (Array k o) (a, i) Source # 
type ElementPtrType (Array k o) (a, i) = ElementPtrType o 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

(Natural n, Show a) => Show (Vector n a) Source # 

Methods

showsPrec :: Int -> Vector n a -> ShowS #

show :: Vector n a -> String #

showList :: [Vector n a] -> ShowS #

(Positive n, IsPrimitive a, IsSized a, Natural ((:*:) n (SizeOf a))) => IsSized (Vector n a) Source # 

Associated Types

type SizeOf (Vector n a) :: * Source #

(Positive n, IsPrimitive a) => IsFirstClass (Vector n a) Source # 
(Positive n, IsPrimitive a) => IsScalarOrVector (Vector n a) Source # 

Associated Types

type NumberOfElements (Vector n a) :: * Source #

(Positive n, IsPrimitive a, IsFloating a) => IsFloating (Vector n a) Source # 
(Positive n, IsPrimitive a, IsInteger a) => IsIntegerOrPointer (Vector n a) Source # 
(Positive n, IsPrimitive a, IsInteger a) => IsInteger (Vector n a) Source # 

Associated Types

type Signed (Vector n a) :: * Source #

(Positive n, IsPrimitive a, IsArithmetic a) => IsArithmetic (Vector n a) Source # 
(Positive n, IsPrimitive a) => IsType (Vector n a) Source # 

Methods

typeDesc :: Proxy (Vector n a) -> TypeDesc Source #

(IsPrimitive a, IsConst a, Positive n) => IsConst (Vector n a) Source # 

Methods

constOf :: Vector n a -> ConstValue (Vector n a) Source #

(CmpRet a, IsPrimitive a, Positive n) => CmpRet (Vector n a) Source # 

Associated Types

type CmpResult (Vector n a) :: * Source #

Methods

cmpBld :: Proxy (Vector n a) -> CmpPredicate -> FFIBinOp

cmpCnst :: Proxy (Vector n a) -> CmpPredicate -> FFIConstBinOp

(Positive n, IsPrimitive a, CallIntrinsic a) => CallIntrinsic (Vector n a) Source # 

Methods

callIntrinsic1' :: String -> Value (Vector n a) -> TValue r (Vector n a)

callIntrinsic2' :: String -> Value (Vector n a) -> Value (Vector n a) -> TValue r (Vector n a)

(GetElementPtr o i, IsIndexArg a, Positive k) => GetElementPtr (Vector k o) (a, i) Source # 

Associated Types

type ElementPtrType (Vector k o) (a, i) :: * Source #

Methods

getIxList :: Proxy (Vector k o) -> (a, i) -> [ValueRef]

type SizeOf (Vector n a) Source # 
type SizeOf (Vector n a) = (:*:) n (SizeOf a)
type NumberOfElements (Vector n a) Source # 
type NumberOfElements (Vector n a) = n
type Signed (Vector n a) Source # 
type Signed (Vector n a) = Signed a
type CmpResult (Vector n a) Source # 
type CmpResult (Vector n a) = Vector n (CmpResult a)
type ElementPtrType (Vector k o) (a, i) Source # 
type ElementPtrType (Vector k o) (a, i) = ElementPtrType o i

newtype Struct a Source #

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

Constructors

Struct a 

Instances

Show a => Show (Struct a) Source # 

Methods

showsPrec :: Int -> Struct a -> ShowS #

show :: Struct a -> String #

showList :: [Struct a] -> ShowS #

StructFields as => IsSized (Struct as) Source # 

Associated Types

type SizeOf (Struct as) :: * Source #

StructFields as => IsFirstClass (Struct as) Source # 
StructFields a => IsType (Struct a) Source # 
IsConstFields a => IsConst (Struct a) Source # 

Methods

constOf :: Struct a -> ConstValue (Struct a) Source #

(GetField as i, Natural i) => GetValue (Struct as) (Proxy i) Source # 

Associated Types

type ValueType (Struct as) (Proxy i) :: * Source #

Methods

getIx :: Proxy (Struct as) -> Proxy i -> CUInt

(GetElementPtr (FieldType fs a) i, Natural a) => GetElementPtr (Struct fs) (Proxy a, i) Source # 

Associated Types

type ElementPtrType (Struct fs) (Proxy a, i) :: * Source #

Methods

getIxList :: Proxy (Struct fs) -> (Proxy a, i) -> [ValueRef]

type SizeOf (Struct as) Source # 
type ValueType (Struct as) (Proxy i) Source # 
type ValueType (Struct as) (Proxy i) = FieldType as i
type ElementPtrType (Struct fs) (Proxy a, i) Source # 
type ElementPtrType (Struct fs) (Proxy a, i) = ElementPtrType (FieldType fs a) i

newtype PackedStruct a Source #

Constructors

PackedStruct a 

Instances

type FixedList n = List n Source #

Values and constants

data Value a Source #

Instances

ToArithFunction r (IO b) (CodeGenFunction r (Value b)) Source # 
ToArithFunction r b0 b1 => ToArithFunction r (a -> b0) (CodeGenFunction r (Value a) -> b1) Source # 

Methods

toArithFunction' :: CodeGenFunction r (Call (a -> b0)) -> CodeGenFunction r (Value a) -> b1

Show (Value a) Source # 

Methods

showsPrec :: Int -> Value a -> ShowS #

show :: Value a -> String #

showList :: [Value a] -> ShowS #

IsIndexArg (Value Int32) Source # 

Methods

getArg :: Value Int32 -> ValueRef

IsIndexArg (Value Int64) Source # 

Methods

getArg :: Value Int64 -> ValueRef

IsIndexArg (Value Word32) Source # 
IsIndexArg (Value Word64) Source # 
AllocArg (Value Word32) Source # 
AUnOp (Value a) Source # 

Methods

aunop :: FFIConstUnOp -> FFIUnOp -> Value a -> CodeGenFunction r (Value a)

IsFirstClass a => Phi (Value a) Source # 
Ret (Value a) a Source # 
CmpRet a => CmpOp (ConstValue a) (Value a) Source # 

Associated Types

type CmpType (ConstValue a) (Value a) :: *

type CmpValue (ConstValue a) (Value a) :: * -> *

Methods

cmpop :: FFIConstBinOp -> FFIBinOp -> ConstValue a -> Value a -> CodeGenFunction r (CmpValueResult (ConstValue a) (Value a))

CmpRet a => CmpOp (Value a) (ConstValue a) Source # 

Associated Types

type CmpType (Value a) (ConstValue a) :: *

type CmpValue (Value a) (ConstValue a) :: * -> *

Methods

cmpop :: FFIConstBinOp -> FFIBinOp -> Value a -> ConstValue a -> CodeGenFunction r (CmpValueResult (Value a) (ConstValue a))

CmpRet a => CmpOp (Value a) (Value a) Source # 

Associated Types

type CmpType (Value a) (Value a) :: *

type CmpValue (Value a) (Value a) :: * -> *

Methods

cmpop :: FFIConstBinOp -> FFIBinOp -> Value a -> Value a -> CodeGenFunction r (CmpValueResult (Value a) (Value a))

ABinOp (ConstValue a) (Value a) Source # 

Associated Types

type ABinOpResult (ConstValue a) (Value a) :: * Source #

Methods

abinop :: FFIConstBinOp -> FFIBinOp -> ConstValue a -> Value a -> CodeGenFunction r (ABinOpResult (ConstValue a) (Value a))

ABinOp (Value a) (ConstValue a) Source # 

Associated Types

type ABinOpResult (Value a) (ConstValue a) :: * Source #

Methods

abinop :: FFIConstBinOp -> FFIBinOp -> Value a -> ConstValue a -> CodeGenFunction r (ABinOpResult (Value a) (ConstValue a))

ABinOp (Value a) (Value a) Source # 

Associated Types

type ABinOpResult (Value a) (Value a) :: * Source #

Methods

abinop :: FFIConstBinOp -> FFIBinOp -> Value a -> Value a -> CodeGenFunction r (ABinOpResult (Value a) (Value a))

CallArgs (IO a) (CodeGenFunction r (Value a)) r Source # 

Associated Types

type CalledFunction (CodeGenFunction r (Value a)) :: *

type CallerResult (CodeGenFunction r (Value a)) :: *

type CallerFunction (IO a) r :: *

Methods

doCall :: Call (IO a) -> CodeGenFunction r (Value a)

CallArgs b b' r => CallArgs (a -> b) (Value a -> b') r Source # 

Associated Types

type CalledFunction (Value a -> b') :: *

type CallerResult (Value a -> b') :: *

type CallerFunction (a -> b) r :: *

Methods

doCall :: Call (a -> b) -> Value a -> b'

type ABinOpResult (ConstValue a) (Value a) Source # 
type ABinOpResult (Value a) (ConstValue a) Source # 
type ABinOpResult (Value a) (Value a) Source # 
type ABinOpResult (Value a) (Value a) = Value a

data ConstValue a Source #

Instances

Show (ConstValue a) Source # 
IsIndexArg (ConstValue Int32) Source # 
IsIndexArg (ConstValue Int64) Source # 
IsIndexArg (ConstValue Word32) Source # 
IsIndexArg (ConstValue Word64) Source # 
AllocArg (ConstValue Word32) Source # 
AUnOp (ConstValue a) Source # 

Methods

aunop :: FFIConstUnOp -> FFIUnOp -> ConstValue a -> CodeGenFunction r (ConstValue a)

CmpRet a => CmpOp (ConstValue a) (ConstValue a) Source # 

Associated Types

type CmpType (ConstValue a) (ConstValue a) :: *

type CmpValue (ConstValue a) (ConstValue a) :: * -> *

Methods

cmpop :: FFIConstBinOp -> FFIBinOp -> ConstValue a -> ConstValue a -> CodeGenFunction r (CmpValueResult (ConstValue a) (ConstValue a))

CmpRet a => CmpOp (ConstValue a) (Value a) Source # 

Associated Types

type CmpType (ConstValue a) (Value a) :: *

type CmpValue (ConstValue a) (Value a) :: * -> *

Methods

cmpop :: FFIConstBinOp -> FFIBinOp -> ConstValue a -> Value a -> CodeGenFunction r (CmpValueResult (ConstValue a) (Value a))

CmpRet a => CmpOp (Value a) (ConstValue a) Source # 

Associated Types

type CmpType (Value a) (ConstValue a) :: *

type CmpValue (Value a) (ConstValue a) :: * -> *

Methods

cmpop :: FFIConstBinOp -> FFIBinOp -> Value a -> ConstValue a -> CodeGenFunction r (CmpValueResult (Value a) (ConstValue a))

ABinOp (ConstValue a) (ConstValue a) Source # 

Associated Types

type ABinOpResult (ConstValue a) (ConstValue a) :: * Source #

Methods

abinop :: FFIConstBinOp -> FFIBinOp -> ConstValue a -> ConstValue a -> CodeGenFunction r (ABinOpResult (ConstValue a) (ConstValue a))

ABinOp (ConstValue a) (Value a) Source # 

Associated Types

type ABinOpResult (ConstValue a) (Value a) :: * Source #

Methods

abinop :: FFIConstBinOp -> FFIBinOp -> ConstValue a -> Value a -> CodeGenFunction r (ABinOpResult (ConstValue a) (Value a))

ABinOp (Value a) (ConstValue a) Source # 

Associated Types

type ABinOpResult (Value a) (ConstValue a) :: * Source #

Methods

abinop :: FFIConstBinOp -> FFIBinOp -> Value a -> ConstValue a -> CodeGenFunction r (ABinOpResult (Value a) (ConstValue a))

type ABinOpResult (ConstValue a) (ConstValue a) Source # 
type ABinOpResult (ConstValue a) (Value a) Source # 
type ABinOpResult (Value a) (ConstValue a) Source # 

valueOf :: IsConst a => a -> Value a Source #

zero :: forall a. IsType a => ConstValue a Source #

allOnes :: forall a. IsInteger a => ConstValue a Source #

undef :: forall a. IsType a => ConstValue a Source #

createString :: String -> TGlobal (Array n Word8) Source #

Deprecated: use withString instead

createStringNul :: String -> TGlobal (Array n Word8) Source #

Deprecated: use withStringNul instead

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 a Source #

fromVector :: MkVector n a => Vector n a -> Tuple n a Source #

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

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

data CodeGenFunction r a Source #

Instances

ArithFunction r z b0 b1 => ArithFunction r z (CodeGenFunction r a -> b0) (a -> b1) Source # 

Methods

arithFunction' :: (CodeGenFunction r a -> b0) -> a -> b1

Ret a r => ArithFunction r a (CodeGenFunction r a) (CodeGenFunction r ()) Source # 
ToArithFunction r (IO b) (CodeGenFunction r (Value b)) Source # 
ToArithFunction r b0 b1 => ToArithFunction r (a -> b0) (CodeGenFunction r (Value a) -> b1) Source # 

Methods

toArithFunction' :: CodeGenFunction r (Call (a -> b0)) -> CodeGenFunction r (Value a) -> b1

Monad (CodeGenFunction r) Source # 
Functor (CodeGenFunction r) Source # 

Methods

fmap :: (a -> b) -> CodeGenFunction r a -> CodeGenFunction r b #

(<$) :: a -> CodeGenFunction r b -> CodeGenFunction r a #

Applicative (CodeGenFunction r) Source # 
MonadIO (CodeGenFunction r) Source # 

Methods

liftIO :: IO a -> CodeGenFunction r a #

CallArgs (IO a) (CodeGenFunction r (Value a)) r Source # 

Associated Types

type CalledFunction (CodeGenFunction r (Value a)) :: *

type CallerResult (CodeGenFunction r (Value a)) :: *

type CallerFunction (IO a) r :: *

Methods

doCall :: Call (IO a) -> CodeGenFunction r (Value a)

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.

newNamedFunction Source #

Arguments

:: IsFunction a 
=> Linkage 
-> String

Function name

-> CodeGenModule (Function a) 

Create a new named function.

defineFunction Source #

Arguments

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

createFunction Source #

Arguments

:: FunctionArgs f 
=> Linkage 
-> FunctionCodeGen f

Function body.

-> CodeGenModule (Function f) 

Create a new function with the given body.

createNamedFunction Source #

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 a Source #

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 a Source #

Create a new global variable.

newNamedGlobal Source #

Arguments

:: 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 a Source #

Create and define a global variable.

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

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.

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 GlobalMappings Source #

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.

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.

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, Value)] Source #

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

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

hasUsers :: Value -> IO Bool Source #

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

getUses :: Value -> IO [Use] Source #

getUser :: Use -> IO Value Source #

isChildOf :: BasicBlock -> Value -> IO Bool Source #

getDep :: Use -> IO (String, String) Source #

Misc

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

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

castVarArgs :: CastVarArgs a b => Function a -> Function b Source #

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 String Source #

Get the name of a Value.

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