Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data LLVM a
- runLLVM :: LLVM a -> (a, Module)
- emitTypeDecl :: TypeDecl -> LLVM ()
- emitGlobal :: Global -> LLVM ()
- emitDeclare :: Declare -> LLVM ()
- emitDefine :: Define -> LLVM ()
- alias :: Ident -> Type -> LLVM ()
- freshSymbol :: LLVM Symbol
- data a :> b = a :> b
- define :: DefineArgs sig k => FunAttrs -> Type -> Symbol -> sig -> k -> LLVM (Typed Value)
- defineFresh :: DefineArgs sig k => FunAttrs -> Type -> sig -> k -> LLVM (Typed Value)
- class DefineArgs a k | a -> k
- define' :: FunAttrs -> Type -> Symbol -> [Type] -> Bool -> ([Typed Value] -> BB ()) -> LLVM (Typed Value)
- declare :: Type -> Symbol -> [Type] -> Bool -> LLVM ()
- global :: Symbol -> Typed Value -> LLVM ()
- iT :: Int32 -> Type
- ptrT :: Type -> Type
- voidT :: Type
- arrayT :: Int32 -> Type -> Type
- (=:) :: Type -> a -> Typed a
- (-:) :: IsValue a => Type -> a -> Typed Value
- class IsValue a where
- int :: Int -> Value
- integer :: Integer -> Value
- struct :: Bool -> [Typed Value] -> Typed Value
- array :: Type -> [Value] -> Typed Value
- string :: Symbol -> String -> LLVM ()
- data BB a
- freshLabel :: BB Ident
- label :: Ident -> BB ()
- comment :: String -> BB ()
- ret :: IsValue a => Typed a -> BB ()
- retVoid :: BB ()
- jump :: Ident -> BB ()
- br :: IsValue a => Typed a -> Ident -> Ident -> BB ()
- unreachable :: BB ()
- unwind :: BB ()
- add :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- fadd :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- sub :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- fsub :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- mul :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- fmul :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- udiv :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- sdiv :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- fdiv :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- urem :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- srem :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- frem :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- shl :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- lshr :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- ashr :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- band :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- bor :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- bxor :: (IsValue a, IsValue b) => Typed a -> b -> BB (Typed Value)
- trunc :: IsValue a => Typed a -> Type -> BB (Typed Value)
- zext :: IsValue a => Typed a -> Type -> BB (Typed Value)
- sext :: IsValue a => Typed a -> Type -> BB (Typed Value)
- fptrunc :: IsValue a => Typed a -> Type -> BB (Typed Value)
- fpext :: IsValue a => Typed a -> Type -> BB (Typed Value)
- fptoui :: IsValue a => Typed a -> Type -> BB (Typed Value)
- fptosi :: IsValue a => Typed a -> Type -> BB (Typed Value)
- uitofp :: IsValue a => Typed a -> Type -> BB (Typed Value)
- sitofp :: IsValue a => Typed a -> Type -> BB (Typed Value)
- ptrtoint :: IsValue a => Typed a -> Type -> BB (Typed Value)
- inttoptr :: IsValue a => Typed a -> Type -> BB (Typed Value)
- bitcast :: IsValue a => Typed a -> Type -> BB (Typed Value)
- extractValue :: IsValue a => Typed a -> Int32 -> BB (Typed Value)
- insertValue :: (IsValue a, IsValue b) => Typed a -> Typed b -> Int32 -> BB (Typed Value)
- alloca :: Type -> Maybe (Typed Value) -> Maybe Int -> BB (Typed Value)
- load :: IsValue a => Typed a -> Maybe Align -> BB (Typed Value)
- store :: (IsValue a, IsValue b) => a -> Typed b -> Maybe Align -> BB ()
- getelementptr :: IsValue a => Type -> Typed a -> [Typed Value] -> BB (Typed Value)
- nullPtr :: Type -> Typed Value
- icmp :: (IsValue a, IsValue b) => ICmpOp -> Typed a -> b -> BB (Typed Value)
- fcmp :: (IsValue a, IsValue b) => FCmpOp -> Typed a -> b -> BB (Typed Value)
- phi :: Type -> [PhiArg] -> BB (Typed Value)
- data PhiArg
- from :: IsValue a => a -> BlockLabel -> PhiArg
- select :: (IsValue a, IsValue b, IsValue c) => Typed a -> Typed b -> Typed c -> BB (Typed Value)
- call :: IsValue a => Typed a -> [Typed Value] -> BB (Typed Value)
- call_ :: IsValue a => Typed a -> [Typed Value] -> BB ()
- invoke :: IsValue a => Type -> a -> [Typed Value] -> Ident -> Ident -> BB (Typed Value)
- shuffleVector :: (IsValue a, IsValue b, IsValue c) => Typed a -> b -> c -> BB (Typed Value)
- module Text.LLVM.AST
LLVM Monad
emitTypeDecl :: TypeDecl -> LLVM () Source
emitGlobal :: Global -> LLVM () Source
emitDeclare :: Declare -> LLVM () Source
emitDefine :: Define -> LLVM () Source
Alias Introduction
Function Definition
a :> b infixr 0 |
(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 -> k Source
Types that can be used to define the body of a function.
defineBody
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.
Types
Values
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
freshLabel :: BB Ident Source
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.
Terminator Instructions
ret :: IsValue a => Typed a -> BB () Source
Emit the ``ret'' instruction and terminate the current basic block.
unreachable :: BB () Source
Binary Operations
Bitwise Binary Operations
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
Other Operations
from :: IsValue a => a -> BlockLabel -> PhiArg 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.
Re-exported
module Text.LLVM.AST