llvm-hs-pure-5.1.0: Pure Haskell LLVM functionality (no FFI).

Safe HaskellSafe
LanguageHaskell98

LLVM.AST.Constant

Description

A representation of LLVM constants

Synopsis

Documentation

data Constant Source #

http://llvm.org/docs/LangRef.html#constants

N.B. - http://llvm.org/docs/LangRef.html#constant-expressions

Although constant expressions and instructions have many similarites, there are important differences - so they're represented using different types in this AST. At the cost of making it harder to move an code back and forth between being constant and not, this approach embeds more of the rules of what IR is legal into the Haskell types.

Constructors

Int 
Float 
Null 

Fields

Struct 
Array 
Vector 

Fields

Undef 

Fields

BlockAddress 
GlobalReference Type Name 
TokenNone 
Add 
FAdd 
Sub 
FSub 
Mul 
FMul 
UDiv 
SDiv 
FDiv 
URem 
SRem 
FRem 
Shl 
LShr 
AShr 
And 
Or 
Xor 
GetElementPtr 
Trunc 

Fields

ZExt 

Fields

SExt 

Fields

FPToUI 

Fields

FPToSI 

Fields

UIToFP 

Fields

SIToFP 

Fields

FPTrunc 

Fields

FPExt 

Fields

PtrToInt 

Fields

IntToPtr 

Fields

BitCast 

Fields

AddrSpaceCast 

Fields

ICmp 
FCmp 
Select 
ExtractElement 

Fields

InsertElement 
ShuffleVector 
ExtractValue 
InsertValue 

Instances

Eq Constant Source # 
Data Constant Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Constant -> c Constant #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Constant #

toConstr :: Constant -> Constr #

dataTypeOf :: Constant -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Constant) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Constant) #

gmapT :: (forall b. Data b => b -> b) -> Constant -> Constant #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Constant -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Constant -> r #

gmapQ :: (forall d. Data d => d -> u) -> Constant -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Constant -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Constant -> m Constant #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Constant -> m Constant #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Constant -> m Constant #

Ord Constant Source # 
Read Constant Source # 
Show Constant Source # 
Generic Constant Source # 

Associated Types

type Rep Constant :: * -> * #

Methods

from :: Constant -> Rep Constant x #

to :: Rep Constant x -> Constant #

type Rep Constant Source # 
type Rep Constant = D1 * (MetaData "Constant" "LLVM.AST.Constant" "llvm-hs-pure-5.1.0-ABIfIqE2ohGHl8oRFKMmj0" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Int" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "integerBits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word32)) (S1 * (MetaSel (Just Symbol "integerValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Integer)))) ((:+:) * (C1 * (MetaCons "Float" PrefixI True) (S1 * (MetaSel (Just Symbol "floatValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * SomeFloat))) (C1 * (MetaCons "Null" PrefixI True) (S1 * (MetaSel (Just Symbol "constantType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type))))) ((:+:) * (C1 * (MetaCons "Struct" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "structName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Name))) ((:*:) * (S1 * (MetaSel (Just Symbol "isPacked") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "memberValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Constant]))))) ((:+:) * (C1 * (MetaCons "Array" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "memberType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Just Symbol "memberValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Constant])))) (C1 * (MetaCons "Vector" PrefixI True) (S1 * (MetaSel (Just Symbol "memberValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Constant])))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Undef" PrefixI True) (S1 * (MetaSel (Just Symbol "constantType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type))) ((:+:) * (C1 * (MetaCons "BlockAddress" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "blockAddressFunction") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Name)) (S1 * (MetaSel (Just Symbol "blockAddressBlock") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Name)))) (C1 * (MetaCons "GlobalReference" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Name)))))) ((:+:) * (C1 * (MetaCons "TokenNone" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Add" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nsw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "nuw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant))))) (C1 * (MetaCons "FAdd" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Sub" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nsw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "nuw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant))))) ((:+:) * (C1 * (MetaCons "FSub" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)))) (C1 * (MetaCons "Mul" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nsw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "nuw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant))))))) ((:+:) * (C1 * (MetaCons "FMul" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)))) ((:+:) * (C1 * (MetaCons "UDiv" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "exact") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant))))) (C1 * (MetaCons "SDiv" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "exact") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "FDiv" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)))) ((:+:) * (C1 * (MetaCons "URem" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)))) (C1 * (MetaCons "SRem" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "FRem" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)))) (C1 * (MetaCons "Shl" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nsw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "nuw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)))))) ((:+:) * (C1 * (MetaCons "LShr" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "exact") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant))))) (C1 * (MetaCons "AShr" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "exact") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)))))))))) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "And" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)))) ((:+:) * (C1 * (MetaCons "Or" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)))) (C1 * (MetaCons "Xor" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)))))) ((:+:) * (C1 * (MetaCons "GetElementPtr" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "inBounds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "address") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "indices") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Constant]))))) ((:+:) * (C1 * (MetaCons "Trunc" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)))) (C1 * (MetaCons "ZExt" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "SExt" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)))) ((:+:) * (C1 * (MetaCons "FPToUI" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)))) (C1 * (MetaCons "FPToSI" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)))))) ((:+:) * (C1 * (MetaCons "UIToFP" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)))) ((:+:) * (C1 * (MetaCons "SIToFP" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)))) (C1 * (MetaCons "FPTrunc" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "FPExt" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)))) ((:+:) * (C1 * (MetaCons "PtrToInt" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)))) (C1 * (MetaCons "IntToPtr" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)))))) ((:+:) * (C1 * (MetaCons "BitCast" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)))) ((:+:) * (C1 * (MetaCons "AddrSpaceCast" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "type'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Type)))) (C1 * (MetaCons "ICmp" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "iPredicate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * IntegerPredicate)) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "FCmp" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "fpPredicate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FloatingPointPredicate)) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant))))) ((:+:) * (C1 * (MetaCons "Select" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "condition'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) ((:*:) * (S1 * (MetaSel (Just Symbol "trueValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "falseValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant))))) (C1 * (MetaCons "ExtractElement" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "vector") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "index") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "InsertElement" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "vector") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) ((:*:) * (S1 * (MetaSel (Just Symbol "element") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "index") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant))))) (C1 * (MetaCons "ShuffleVector" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "operand0") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) ((:*:) * (S1 * (MetaSel (Just Symbol "operand1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "mask") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)))))) ((:+:) * (C1 * (MetaCons "ExtractValue" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "aggregate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "indices'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Word32])))) (C1 * (MetaCons "InsertValue" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "aggregate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) ((:*:) * (S1 * (MetaSel (Just Symbol "element") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Constant)) (S1 * (MetaSel (Just Symbol "indices'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Word32])))))))))))

signedIntegerValue :: Constant -> Integer Source #

Since LLVM types don't include signedness, there's ambiguity in interpreting an constant as an Integer. The LLVM assembly printer prints integers as signed, but cheats for 1-bit integers and prints them as true or false. That way it circuments the otherwise awkward fact that a twos complement 1-bit number only has the values -1 and 0.

unsignedIntegerValue :: Constant -> Integer Source #

This library's conversion from LLVM C++ objects will always produce integer constants as unsigned, so this function in many cases is not necessary. However, nothing's to keep stop direct construction of an Int with a negative integerValue. There's nothing in principle wrong with such a value - it has perfectly good low order bits like any integer, and will be used as such, likely producing the intended result if lowered to C++. If, however one wishes to interpret an Int of unknown provenance as unsigned, then this function will serve.