llvm-pretty-0.12.0.0: A pretty printing library inspired by the llvm binding.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.LLVM

Synopsis

LLVM Monad

data LLVM a Source #

Instances

Instances details
MonadFix LLVM Source # 
Instance details

Defined in Text.LLVM

Methods

mfix :: (a -> LLVM a) -> LLVM a #

Applicative LLVM Source # 
Instance details

Defined in Text.LLVM

Methods

pure :: a -> LLVM a #

(<*>) :: LLVM (a -> b) -> LLVM a -> LLVM b #

liftA2 :: (a -> b -> c) -> LLVM a -> LLVM b -> LLVM c #

(*>) :: LLVM a -> LLVM b -> LLVM b #

(<*) :: LLVM a -> LLVM b -> LLVM a #

Functor LLVM Source # 
Instance details

Defined in Text.LLVM

Methods

fmap :: (a -> b) -> LLVM a -> LLVM b #

(<$) :: a -> LLVM b -> LLVM a #

Monad LLVM Source # 
Instance details

Defined in Text.LLVM

Methods

(>>=) :: LLVM a -> (a -> LLVM b) -> LLVM b #

(>>) :: LLVM a -> LLVM b -> LLVM b #

return :: a -> LLVM a #

runLLVM :: LLVM a -> (a, Module) Source #

Alias Introduction

alias :: Ident -> Type -> LLVM () Source #

Function Definition

data a :> b infixr 0 Source #

Constructors

a :> b infixr 0 

Instances

Instances details
(Show a, Show b) => Show (a :> b) Source # 
Instance details

Defined in Text.LLVM

Methods

showsPrec :: Int -> (a :> b) -> ShowS #

show :: (a :> b) -> String #

showList :: [a :> b] -> ShowS #

DefineArgs as k => DefineArgs (Type :> as) (Typed Value -> k) Source # 
Instance details

Defined in Text.LLVM

Methods

defineBody :: [Typed Ident] -> (Type :> as) -> (Typed Value -> k) -> LLVM ([Typed Ident], [BasicBlock])

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.

Minimal complete definition

defineBody

Instances

Instances details
DefineArgs () (BB ()) Source # 
Instance details

Defined in Text.LLVM

Methods

defineBody :: [Typed Ident] -> () -> BB () -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs Type (Typed Value -> BB ()) Source # 
Instance details

Defined in Text.LLVM

Methods

defineBody :: [Typed Ident] -> Type -> (Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs as k => DefineArgs (Type :> as) (Typed Value -> k) Source # 
Instance details

Defined in Text.LLVM

Methods

defineBody :: [Typed Ident] -> (Type :> as) -> (Typed Value -> k) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs (Type, Type) (Typed Value -> Typed Value -> BB ()) Source # 
Instance details

Defined in Text.LLVM

Methods

defineBody :: [Typed Ident] -> (Type, Type) -> (Typed Value -> Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs (Type, Type, Type) (Typed Value -> Typed Value -> Typed Value -> BB ()) Source # 
Instance details

Defined in Text.LLVM

Methods

defineBody :: [Typed Ident] -> (Type, Type, Type) -> (Typed Value -> Typed Value -> Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

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 (Typed Value) Source #

Emit a declaration.

global :: GlobalAttrs -> Symbol -> Type -> Maybe Value -> LLVM (Typed Value) Source #

Emit a global declaration.

data FunAttrs Source #

Instances

Instances details
Show FunAttrs Source # 
Instance details

Defined in Text.LLVM

Types

(=:) :: Type -> a -> Typed a Source #

(-:) :: IsValue a => Type -> a -> Typed Value Source #

Values

class IsValue a where Source #

Methods

toValue :: a -> Value Source #

Instances

Instances details
IsValue Int16 Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Int16 -> Value Source #

IsValue Int32 Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Int32 -> Value Source #

IsValue Int64 Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Int64 -> Value Source #

IsValue Int8 Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Int8 -> Value Source #

IsValue Ident Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Ident -> Value Source #

IsValue Symbol Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Symbol -> Value Source #

IsValue Value Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Value -> Value Source #

IsValue Integer Source # 
Instance details

Defined in Text.LLVM

IsValue Bool Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Bool -> Value Source #

IsValue Double Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Double -> Value Source #

IsValue Float Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Float -> Value Source #

IsValue Int Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Int -> Value Source #

IsValue a => IsValue (Typed a) Source # 
Instance details

Defined in Text.LLVM

Methods

toValue :: Typed a -> Value Source #

string :: Symbol -> String -> LLVM (Typed Value) 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

Instances details
MonadFix BB Source # 
Instance details

Defined in Text.LLVM

Methods

mfix :: (a -> BB a) -> BB a #

Applicative BB Source # 
Instance details

Defined in Text.LLVM

Methods

pure :: a -> BB a #

(<*>) :: BB (a -> b) -> BB a -> BB b #

liftA2 :: (a -> b -> c) -> BB a -> BB b -> BB c #

(*>) :: BB a -> BB b -> BB b #

(<*) :: BB a -> BB b -> BB a #

Functor BB Source # 
Instance details

Defined in Text.LLVM

Methods

fmap :: (a -> b) -> BB a -> BB b #

(<$) :: a -> BB b -> BB a #

Monad BB Source # 
Instance details

Defined in Text.LLVM

Methods

(>>=) :: BB a -> (a -> BB b) -> BB b #

(>>) :: BB a -> BB b -> BB b #

return :: a -> BB a #

DefineArgs () (BB ()) Source # 
Instance details

Defined in Text.LLVM

Methods

defineBody :: [Typed Ident] -> () -> BB () -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs Type (Typed Value -> BB ()) Source # 
Instance details

Defined in Text.LLVM

Methods

defineBody :: [Typed Ident] -> Type -> (Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

IsString (BB a) Source # 
Instance details

Defined in Text.LLVM

Methods

fromString :: String -> BB a #

DefineArgs (Type, Type) (Typed Value -> Typed Value -> BB ()) Source # 
Instance details

Defined in Text.LLVM

Methods

defineBody :: [Typed Ident] -> (Type, Type) -> (Typed Value -> Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

DefineArgs (Type, Type, Type) (Typed Value -> Typed Value -> Typed Value -> BB ()) Source # 
Instance details

Defined in Text.LLVM

Methods

defineBody :: [Typed Ident] -> (Type, Type, Type) -> (Typed Value -> Typed Value -> Typed Value -> BB ()) -> LLVM ([Typed Ident], [BasicBlock])

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.

assign :: IsValue a => Ident -> BB (Typed a) -> BB (Typed Value) Source #

Emit an assignment that uses the given identifier to name the result of the BB operation.

WARNING: this can throw errors.

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.

jump :: Ident -> BB () Source #

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

zext :: IsValue a => Typed a -> Type -> BB (Typed Value) Source #

sext :: IsValue a => Typed a -> Type -> BB (Typed Value) Source #

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

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.

switch :: IsValue a => Typed a -> Ident -> [(Integer, Ident)] -> BB () Source #

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

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

Re-exported