llvm-pretty-0.3.0.0: A pretty printing library inspired by the llvm binding.

Safe HaskellNone

Text.LLVM

Contents

Synopsis

LLVM Monad

data LLVM a Source

Instances

Monad LLVM 
Functor LLVM 
MonadFix LLVM 
Applicative LLVM 

Alias Introduction

Function Definition

data a :> b Source

Constructors

a :> b 

Instances

(Show a, Show b) => Show (:> a b) 
DefineArgs as k => DefineArgs (:> Type as) (Typed Value -> k) 

define :: DefineArgs sig k => FunAttrs -> Type -> Symbol -> sig -> k -> LLVM (Typed Value)Source

Define a function.

defineFresh :: DefineArgs sig k => FunAttrs -> Type -> sig -> k -> LLVM (Typed Value)Source

A combination of define and freshSymbol.

class DefineArgs a k | a -> kSource

Types that can be used to define the body of a function.

Instances

define' :: FunAttrs -> Type -> Symbol -> [Type] -> Bool -> ([Typed Value] -> BB ()) -> LLVM (Typed Value)Source

Function definition when the argument list isn't statically known. This is useful when generating code.

declare :: Type -> Symbol -> [Type] -> Bool -> LLVM ()Source

Emit a declaration.

global :: Symbol -> Typed Value -> LLVM ()Source

Emit a global declaration.

Types

iT :: Int32 -> TypeSource

arrayT :: Int32 -> Type -> TypeSource

(=:) :: Type -> a -> Typed aSource

Values

class IsValue a whereSource

Methods

toValue :: a -> ValueSource

Instances

IsValue Int 
IsValue Int8 
IsValue Int16 
IsValue Int32 
IsValue Int64 
IsValue Integer 
IsValue Value 
IsValue Symbol 
IsValue Ident 
IsValue a => IsValue (Typed a) 

int :: Int -> ValueSource

integer :: Integer -> ValueSource

string :: Symbol -> String -> LLVM ()Source

Output a somewhat clunky representation for a string global, that deals well with escaping in the haskell-source string.

Basic Blocks

data BB a Source

Instances

Monad BB 
Functor BB 
MonadFix BB 
Applicative BB 
DefineArgs () (BB ()) 
DefineArgs Type (Typed Value -> BB ()) 
IsString (BB a) 
DefineArgs (Type, Type) (Typed Value -> Typed Value -> BB ()) 
DefineArgs (Type, Type, Type) (Typed Value -> Typed Value -> Typed Value -> BB ()) 

label :: Ident -> BB ()Source

Force termination of the current basic block, and start a new one with the given label. If the previous block had no instructions defined, it will just be thrown away.

comment :: String -> BB ()Source

Terminator Instructions

ret :: IsValue a => Typed a -> BB ()Source

Emit the `ret' instruction and terminate the current basic block.

retVoid :: BB ()Source

Emit ``ret void'' and terminate the current basic block.

br :: IsValue a => Typed a -> Ident -> Ident -> BB ()Source

Binary Operations

add :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

fadd :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

sub :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

fsub :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

mul :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

fmul :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

udiv :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

sdiv :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

fdiv :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

urem :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

srem :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

frem :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

Bitwise Binary Operations

shl :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

lshr :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

ashr :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

band :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

bor :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

bxor :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)Source

Conversion Operations

Aggregate Operations

extractValue :: IsValue a => Typed a -> Int32 -> BB (Typed Value)Source

Returns the value stored in the member field of an aggregate value.

insertValue :: (IsValue a, IsValue b) => Typed a -> Typed b -> Int32 -> BB (Typed Value)Source

Inserts a value into the member field of an aggregate value, and returns the new value.

Memory Access and Addressing Operations

alloca :: Type -> Maybe (Typed Value) -> Maybe Int -> BB (Typed Value)Source

load :: IsValue a => Typed a -> Maybe Align -> BB (Typed Value)Source

store :: (IsValue a, IsValue b) => a -> Typed b -> Maybe Align -> BB ()Source

Other Operations

icmp :: (IsValue a, IsValue b) => ICmpOp -> Typed a -> b -> BB (Typed Value)Source

fcmp :: (IsValue a, IsValue b) => FCmpOp -> Typed a -> b -> BB (Typed Value)Source

select :: (IsValue a, IsValue b, IsValue c) => Typed a -> Typed b -> Typed c -> BB (Typed Value)Source

call :: IsValue a => Typed a -> [Typed Value] -> BB (Typed Value)Source

Emit a call instruction, and generate a new variable for its result.

call_ :: IsValue a => Typed a -> [Typed Value] -> BB ()Source

Emit a call instruction, but don't generate a new variable for its result.

invoke :: IsValue a => Type -> a -> [Typed Value] -> Ident -> Ident -> BB (Typed Value)Source

Emit an invoke instruction, and generate a new variable for its result.

shuffleVector :: (IsValue a, IsValue b, IsValue c) => Typed a -> b -> c -> BB (Typed Value)Source

Re-exported