llvm-extra-0.12.0.1: Utility functions for the llvm interface
Safe HaskellSafe-Inferred
LanguageHaskell98

LLVM.Extra.Multi.Value

Synopsis

Documentation

newtype T a Source #

Constructors

Cons (Repr a) 

Instances

Instances details
C T Source # 
Instance details

Defined in LLVM.Extra.Multi.Class

Associated Types

type Size T Source #

Methods

switch :: f T -> f (T0 (Size T)) -> f T Source #

Additive a => Additive (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

zero :: T a Source #

add :: T a -> T a -> CodeGenFunction r (T a) Source #

sub :: T a -> T a -> CodeGenFunction r (T a) Source #

neg :: T a -> CodeGenFunction r (T a) Source #

Algebraic a => Algebraic (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

sqrt :: T a -> CodeGenFunction r (T a) Source #

Comparison a => Comparison (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type CmpResult (T a) Source #

Methods

cmp :: CmpPredicate -> T a -> T a -> CodeGenFunction r (CmpResult (T a)) Source #

Field a => Field (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

fdiv :: T a -> T a -> CodeGenFunction r (T a) Source #

FloatingComparison a => FloatingComparison (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

fcmp :: FPPredicate -> T a -> T a -> CodeGenFunction r (CmpResult (T a)) Source #

Fraction a => Fraction (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

truncate :: T a -> CodeGenFunction r (T a) Source #

fraction :: T a -> CodeGenFunction r (T a) Source #

IntegerConstant a => IntegerConstant (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

fromInteger' :: Integer -> T a Source #

Logic a => Logic (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

and :: T a -> T a -> CodeGenFunction r (T a) Source #

or :: T a -> T a -> CodeGenFunction r (T a) Source #

xor :: T a -> T a -> CodeGenFunction r (T a) Source #

inv :: T a -> CodeGenFunction r (T a) Source #

PseudoModule a => PseudoModule (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

scale :: Scalar (T a) -> T a -> CodeGenFunction r (T a) Source #

PseudoRing a => PseudoRing (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

mul :: T a -> T a -> CodeGenFunction r (T a) Source #

RationalConstant a => RationalConstant (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Real a => Real (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

min :: T a -> T a -> CodeGenFunction r (T a) Source #

max :: T a -> T a -> CodeGenFunction r (T a) Source #

abs :: T a -> CodeGenFunction r (T a) Source #

signum :: T a -> CodeGenFunction r (T a) Source #

Transcendental a => Transcendental (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

pi :: CodeGenFunction r (T a) Source #

sin :: T a -> CodeGenFunction r (T a) Source #

cos :: T a -> CodeGenFunction r (T a) Source #

exp :: T a -> CodeGenFunction r (T a) Source #

log :: T a -> CodeGenFunction r (T a) Source #

pow :: T a -> T a -> CodeGenFunction r (T a) Source #

Select a => Select (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

select :: Value Bool -> T a -> T a -> CodeGenFunction r (T a) Source #

(IsType (Struct (Repr a)), IsSized (Struct (Repr a)), C a, C (Repr a)) => C (T a) Source # 
Instance details

Defined in LLVM.Extra.Memory

Associated Types

type Struct (T a) Source #

Methods

load :: Value (Ptr (Struct (T a))) -> CodeGenFunction r (T a) Source #

store :: T a -> Value (Ptr (Struct (T a))) -> CodeGenFunction r () Source #

decompose :: Value (Struct (T a)) -> CodeGenFunction r (T a) Source #

compose :: T a -> CodeGenFunction r (Value (Struct (T a))) Source #

Compose (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Composed (T a) Source #

Methods

compose :: T a -> T (Composed (T a)) Source #

C a => Phi (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

phi :: BasicBlock -> T a -> CodeGenFunction r (T a) Source #

addPhi :: BasicBlock -> T a -> T a -> CodeGenFunction r () Source #

C a => Undefined (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

undef :: T a Source #

C a => Zero (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

zero :: T a Source #

type Size T Source # 
Instance details

Defined in LLVM.Extra.Multi.Class

type Size T = D1
type CmpResult (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type CmpResult (T a) = T Bool
type Scalar (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type Scalar (T a) = T (Scalar a)
type Struct (T a) Source # 
Instance details

Defined in LLVM.Extra.Memory

type Struct (T a) = Struct (Repr a)
type Composed (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type Composed (T a) = a

class C a where Source #

Associated Types

type Repr a Source #

Methods

cons :: a -> T a Source #

undef :: T a Source #

zero :: T a Source #

phi :: BasicBlock -> T a -> CodeGenFunction r (T a) Source #

addPhi :: BasicBlock -> T a -> T a -> CodeGenFunction r () Source #

Instances

Instances details
C Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr Int16 Source #

C Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr Int32 Source #

C Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr Int64 Source #

C Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr Int8 Source #

C Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr Word16 Source #

C Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr Word32 Source #

C Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr Word64 Source #

C Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr Word8 Source #

C Bool8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr Bool8 Source #

C () Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr () Source #

Methods

cons :: () -> T () Source #

undef :: T () Source #

zero :: T () Source #

phi :: BasicBlock -> T () -> CodeGenFunction r (T ()) Source #

addPhi :: BasicBlock -> T () -> T () -> CodeGenFunction r () Source #

C Bool Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr Bool Source #

C Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr Double Source #

C Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr Float Source #

C Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr Int Source #

C Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr Word Source #

C a => C (Complex a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (Complex a) Source #

IsFunction a => C (FunPtr a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (FunPtr a) Source #

Methods

cons :: FunPtr a -> T (FunPtr a) Source #

undef :: T (FunPtr a) Source #

zero :: T (FunPtr a) Source #

phi :: BasicBlock -> T (FunPtr a) -> CodeGenFunction r (T (FunPtr a)) Source #

addPhi :: BasicBlock -> T (FunPtr a) -> T (FunPtr a) -> CodeGenFunction r () Source #

C (Ptr a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (Ptr a) Source #

Methods

cons :: Ptr a -> T (Ptr a) Source #

undef :: T (Ptr a) Source #

zero :: T (Ptr a) Source #

phi :: BasicBlock -> T (Ptr a) -> CodeGenFunction r (T (Ptr a)) Source #

addPhi :: BasicBlock -> T (Ptr a) -> T (Ptr a) -> CodeGenFunction r () Source #

C (StablePtr a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (StablePtr a) Source #

Struct struct => C (T struct) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (T struct) Source #

Methods

cons :: T struct -> T0 (T struct) Source #

undef :: T0 (T struct) Source #

zero :: T0 (T struct) Source #

phi :: BasicBlock -> T0 (T struct) -> CodeGenFunction r (T0 (T struct)) Source #

addPhi :: BasicBlock -> T0 (T struct) -> T0 (T struct) -> CodeGenFunction r () Source #

Positive n => C (IntN n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (IntN n) Source #

Methods

cons :: IntN n -> T (IntN n) Source #

undef :: T (IntN n) Source #

zero :: T (IntN n) Source #

phi :: BasicBlock -> T (IntN n) -> CodeGenFunction r (T (IntN n)) Source #

addPhi :: BasicBlock -> T (IntN n) -> T (IntN n) -> CodeGenFunction r () Source #

IsType a => C (Ptr a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (Ptr a) Source #

Methods

cons :: Ptr a -> T (Ptr a) Source #

undef :: T (Ptr a) Source #

zero :: T (Ptr a) Source #

phi :: BasicBlock -> T (Ptr a) -> CodeGenFunction r (T (Ptr a)) Source #

addPhi :: BasicBlock -> T (Ptr a) -> T (Ptr a) -> CodeGenFunction r () Source #

Positive n => C (WordN n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (WordN n) Source #

Methods

cons :: WordN n -> T (WordN n) Source #

undef :: T (WordN n) Source #

zero :: T (WordN n) Source #

phi :: BasicBlock -> T (WordN n) -> CodeGenFunction r (T (WordN n)) Source #

addPhi :: BasicBlock -> T (WordN n) -> T (WordN n) -> CodeGenFunction r () Source #

(IsConst a, IsFirstClass a) => C (Stored a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (Stored a) Source #

Methods

cons :: Stored a -> T (Stored a) Source #

undef :: T (Stored a) Source #

zero :: T (Stored a) Source #

phi :: BasicBlock -> T (Stored a) -> CodeGenFunction r (T (Stored a)) Source #

addPhi :: BasicBlock -> T (Stored a) -> T (Stored a) -> CodeGenFunction r () Source #

C tuple => C (Tuple tuple) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (Tuple tuple) Source #

Methods

cons :: Tuple tuple -> T (Tuple tuple) Source #

undef :: T (Tuple tuple) Source #

zero :: T (Tuple tuple) Source #

phi :: BasicBlock -> T (Tuple tuple) -> CodeGenFunction r (T (Tuple tuple)) Source #

addPhi :: BasicBlock -> T (Tuple tuple) -> T (Tuple tuple) -> CodeGenFunction r () Source #

C a => C (Maybe a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (Maybe a) Source #

Methods

cons :: Maybe a -> T (Maybe a) Source #

undef :: T (Maybe a) Source #

zero :: T (Maybe a) Source #

phi :: BasicBlock -> T (Maybe a) -> CodeGenFunction r (T (Maybe a)) Source #

addPhi :: BasicBlock -> T (Maybe a) -> T (Maybe a) -> CodeGenFunction r () Source #

(IsInteger w, IsConst w) => C (T w i) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (T w i) Source #

Methods

cons :: T w i -> T0 (T w i) Source #

undef :: T0 (T w i) Source #

zero :: T0 (T w i) Source #

phi :: BasicBlock -> T0 (T w i) -> CodeGenFunction r (T0 (T w i)) Source #

addPhi :: BasicBlock -> T0 (T w i) -> T0 (T w i) -> CodeGenFunction r () Source #

MultiValue a => C (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Associated Types

type Repr (Number flags a) Source #

Methods

cons :: Number flags a -> T (Number flags a) Source #

undef :: T (Number flags a) Source #

zero :: T (Number flags a) Source #

phi :: BasicBlock -> T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

addPhi :: BasicBlock -> T (Number flags a) -> T (Number flags a) -> CodeGenFunction r () Source #

(Natural n, C a) => C (Array n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Array

Associated Types

type Repr (Array n a) Source #

Methods

cons :: Array n a -> T (Array n a) Source #

undef :: T (Array n a) Source #

zero :: T (Array n a) Source #

phi :: BasicBlock -> T (Array n a) -> CodeGenFunction r (T (Array n a)) Source #

addPhi :: BasicBlock -> T (Array n a) -> T (Array n a) -> CodeGenFunction r () Source #

(Positive n, C a) => C (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector.Instance

Associated Types

type Repr (Vector n a) Source #

Methods

cons :: Vector n a -> T (Vector n a) Source #

undef :: T (Vector n a) Source #

zero :: T (Vector n a) Source #

phi :: BasicBlock -> T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

addPhi :: BasicBlock -> T (Vector n a) -> T (Vector n a) -> CodeGenFunction r () Source #

(IsInteger w, IsConst w, Num w, Enum e) => C (T w e) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (T w e) Source #

Methods

cons :: T w e -> T0 (T w e) Source #

undef :: T0 (T w e) Source #

zero :: T0 (T w e) Source #

phi :: BasicBlock -> T0 (T w e) -> CodeGenFunction r (T0 (T w e)) Source #

addPhi :: BasicBlock -> T0 (T w e) -> T0 (T w e) -> CodeGenFunction r () Source #

(C a, C b) => C (a, b) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (a, b) Source #

Methods

cons :: (a, b) -> T (a, b) Source #

undef :: T (a, b) Source #

zero :: T (a, b) Source #

phi :: BasicBlock -> T (a, b) -> CodeGenFunction r (T (a, b)) Source #

addPhi :: BasicBlock -> T (a, b) -> T (a, b) -> CodeGenFunction r () Source #

C a => C (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (Tagged tag a) Source #

Methods

cons :: Tagged tag a -> T (Tagged tag a) Source #

undef :: T (Tagged tag a) Source #

zero :: T (Tagged tag a) Source #

phi :: BasicBlock -> T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

addPhi :: BasicBlock -> T (Tagged tag a) -> T (Tagged tag a) -> CodeGenFunction r () Source #

(C a, C b, C c) => C (a, b, c) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (a, b, c) Source #

Methods

cons :: (a, b, c) -> T (a, b, c) Source #

undef :: T (a, b, c) Source #

zero :: T (a, b, c) Source #

phi :: BasicBlock -> T (a, b, c) -> CodeGenFunction r (T (a, b, c)) Source #

addPhi :: BasicBlock -> T (a, b, c) -> T (a, b, c) -> CodeGenFunction r () Source #

(C a, C b, C c, C d) => C (a, b, c, d) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Repr (a, b, c, d) Source #

Methods

cons :: (a, b, c, d) -> T (a, b, c, d) Source #

undef :: T (a, b, c, d) Source #

zero :: T (a, b, c, d) Source #

phi :: BasicBlock -> T (a, b, c, d) -> CodeGenFunction r (T (a, b, c, d)) Source #

addPhi :: BasicBlock -> T (a, b, c, d) -> T (a, b, c, d) -> CodeGenFunction r () Source #

cast :: Repr a ~ Repr b => T a -> T b Source #

consPrimitive :: (IsConst al, Value al ~ Repr a) => al -> T a Source #

undefPrimitive :: (IsType al, Value al ~ Repr a) => T a Source #

zeroPrimitive :: (IsType al, Value al ~ Repr a) => T a Source #

phiPrimitive :: (IsFirstClass al, Value al ~ Repr a) => BasicBlock -> T a -> CodeGenFunction r (T a) Source #

addPhiPrimitive :: (IsFirstClass al, Value al ~ Repr a) => BasicBlock -> T a -> T a -> CodeGenFunction r () Source #

consTuple :: (Value a, Repr a ~ ValueOf a) => a -> T a Source #

undefTuple :: (Repr a ~ al, Undefined al) => T a Source #

zeroTuple :: (Repr a ~ al, Zero al) => T a Source #

phiTuple :: (Repr a ~ al, Phi al) => BasicBlock -> T a -> CodeGenFunction r (T a) Source #

addPhiTuple :: (Repr a ~ al, Phi al) => BasicBlock -> T a -> T a -> CodeGenFunction r () Source #

consUnit :: Repr a ~ () => a -> T a Source #

undefUnit :: Repr a ~ () => T a Source #

zeroUnit :: Repr a ~ () => T a Source #

phiUnit :: Repr a ~ () => BasicBlock -> T a -> CodeGenFunction r (T a) Source #

addPhiUnit :: Repr a ~ () => BasicBlock -> T a -> T a -> CodeGenFunction r () Source #

toEnum :: Repr w ~ Value w => T w -> T (T w e) Source #

fromEnum :: Repr w ~ Value w => T (T w e) -> T w Source #

succ :: (IsArithmetic w, IntegerConstant w) => T (T w e) -> CodeGenFunction r (T (T w e)) Source #

pred :: (IsArithmetic w, IntegerConstant w) => T (T w e) -> CodeGenFunction r (T (T w e)) Source #

cmpEnum :: (CmpRet w, IsPrimitive w) => CmpPredicate -> T (T w a) -> T (T w a) -> CodeGenFunction r (T Bool) Source #

class C a => Bounded a where Source #

Methods

minBound :: T a Source #

maxBound :: T a Source #

Instances

Instances details
(IsInteger w, IsConst w, Num w, Enum e, Bounded e) => Bounded (T w e) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

minBound :: T0 (T w e) Source #

maxBound :: T0 (T w e) Source #

splitMaybe :: T (Maybe a) -> (T Bool, T a) Source #

toMaybe :: T Bool -> T a -> T (Maybe a) Source #

nothing :: C a => T (Maybe a) Source #

just :: T a -> T (Maybe a) Source #

fst :: T (a, b) -> T a Source #

snd :: T (a, b) -> T b Source #

curry :: (T (a, b) -> c) -> T a -> T b -> c Source #

uncurry :: (T a -> T b -> c) -> T (a, b) -> c Source #

mapFst :: (T a0 -> T a1) -> T (a0, b) -> T (a1, b) Source #

mapSnd :: (T b0 -> T b1) -> T (a, b0) -> T (a, b1) Source #

mapFstF :: Functor f => (T a0 -> f (T a1)) -> T (a0, b) -> f (T (a1, b)) Source #

mapSndF :: Functor f => (T b0 -> f (T b1)) -> T (a, b0) -> f (T (a, b1)) Source #

swap :: T (a, b) -> T (b, a) Source #

fst3 :: T (a, b, c) -> T a Source #

snd3 :: T (a, b, c) -> T b Source #

thd3 :: T (a, b, c) -> T c Source #

curry3 :: (T (a, b, c) -> d) -> T a -> T b -> T c -> d Source #

uncurry3 :: (T a -> T b -> T c -> d) -> T (a, b, c) -> d Source #

mapFst3 :: (T a0 -> T a1) -> T (a0, b, c) -> T (a1, b, c) Source #

mapSnd3 :: (T b0 -> T b1) -> T (a, b0, c) -> T (a, b1, c) Source #

mapThd3 :: (T c0 -> T c1) -> T (a, b, c0) -> T (a, b, c1) Source #

mapFst3F :: Functor f => (T a0 -> f (T a1)) -> T (a0, b, c) -> f (T (a1, b, c)) Source #

mapSnd3F :: Functor f => (T b0 -> f (T b1)) -> T (a, b0, c) -> f (T (a, b1, c)) Source #

mapThd3F :: Functor f => (T c0 -> f (T c1)) -> T (a, b, c0) -> f (T (a, b, c1)) Source #

zip :: T a -> T b -> T (a, b) Source #

zip3 :: T a -> T b -> T c -> T (a, b, c) Source #

zip4 :: T a -> T b -> T c -> T d -> T (a, b, c, d) Source #

unzip :: T (a, b) -> (T a, T b) Source #

unzip3 :: T (a, b, c) -> (T a, T b, T c) Source #

unzip4 :: T (a, b, c, d) -> (T a, T b, T c, T d) Source #

tuple :: T tuple -> T (Tuple tuple) Source #

untuple :: T (Tuple tuple) -> T tuple Source #

class Struct struct where Source #

Methods

consStruct :: T struct ~ a => a -> T a Source #

undefStruct :: T struct ~ a => T a Source #

zeroStruct :: T struct ~ a => T a Source #

phiStruct :: T struct ~ a => BasicBlock -> T a -> CodeGenFunction r (T a) Source #

addPhiStruct :: T struct ~ a => BasicBlock -> T a -> T a -> CodeGenFunction r () Source #

Instances

Instances details
Struct () Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

consStruct :: T () ~ a => a -> T a Source #

undefStruct :: T () ~ a => T a Source #

zeroStruct :: T () ~ a => T a Source #

phiStruct :: T () ~ a => BasicBlock -> T a -> CodeGenFunction r (T a) Source #

addPhiStruct :: T () ~ a => BasicBlock -> T a -> T a -> CodeGenFunction r () Source #

(C a, Struct as) => Struct (a, as) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

consStruct :: T (a, as) ~ a0 => a0 -> T a0 Source #

undefStruct :: T (a, as) ~ a0 => T a0 Source #

zeroStruct :: T (a, as) ~ a0 => T a0 Source #

phiStruct :: T (a, as) ~ a0 => BasicBlock -> T a0 -> CodeGenFunction r (T a0) Source #

addPhiStruct :: T (a, as) ~ a0 => BasicBlock -> T a0 -> T a0 -> CodeGenFunction r () Source #

structCons :: T a -> T (T as) -> T (T (a, as)) Source #

structUncons :: T (T (a, as)) -> (T a, T (T as)) Source #

tag :: T a -> T (Tagged tag a) Source #

untag :: T (Tagged tag a) -> T a Source #

liftTaggedM :: Monad m => (T a -> m (T b)) -> T (Tagged tag a) -> m (T (Tagged tag b)) Source #

liftTaggedM2 :: Monad m => (T a -> T b -> m (T c)) -> T (Tagged tag a) -> T (Tagged tag b) -> m (T (Tagged tag c)) Source #

consComplex :: T a -> T a -> T (Complex a) Source #

deconsComplex :: T (Complex a) -> (T a, T a) Source #

class Compose multituple where Source #

Associated Types

type Composed multituple Source #

Methods

compose :: multituple -> T (Composed multituple) Source #

A nested zip.

Instances

Instances details
Compose () Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Composed () Source #

Methods

compose :: () -> T (Composed ()) Source #

Compose a => Compose (Complex a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Composed (Complex a) Source #

Methods

compose :: Complex a -> T (Composed (Complex a)) Source #

Compose (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Composed (T a) Source #

Methods

compose :: T a -> T (Composed (T a)) Source #

Compose tuple => Compose (Tuple tuple) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Composed (Tuple tuple) Source #

Methods

compose :: Tuple tuple -> T (Composed (Tuple tuple)) Source #

(Flags flags, Compose a) => Compose (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Associated Types

type Composed (Number flags a) Source #

Methods

compose :: Number flags a -> T (Composed (Number flags a)) Source #

(Compose a, Compose b) => Compose (a, b) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Composed (a, b) Source #

Methods

compose :: (a, b) -> T (Composed (a, b)) Source #

Compose a => Compose (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Composed (Tagged tag a) Source #

Methods

compose :: Tagged tag a -> T (Composed (Tagged tag a)) Source #

(Compose a, Compose b, Compose c) => Compose (a, b, c) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Composed (a, b, c) Source #

Methods

compose :: (a, b, c) -> T (Composed (a, b, c)) Source #

(Compose a, Compose b, Compose c, Compose d) => Compose (a, b, c, d) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type Composed (a, b, c, d) Source #

Methods

compose :: (a, b, c, d) -> T (Composed (a, b, c, d)) Source #

class Composed (Decomposed T pattern) ~ PatternTuple pattern => Decompose pattern where Source #

Methods

decompose :: pattern -> T (PatternTuple pattern) -> Decomposed T pattern Source #

A nested unzip. Since it is not obvious how deep to decompose nested tuples, you must provide a pattern of the decomposed tuple. E.g.

f :: MultiValue ((a,b),(c,d)) ->
     ((MultiValue a, MultiValue b), MultiValue (c,d))
f = decompose ((atom,atom),atom)

Instances

Instances details
Decompose () Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

decompose :: () -> T (PatternTuple ()) -> Decomposed T () Source #

Decompose pa => Decompose (Complex pa) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Decompose (Atom a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

decompose :: Atom a -> T (PatternTuple (Atom a)) -> Decomposed T (Atom a) Source #

Decompose p => Decompose (Tuple p) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

decompose :: Tuple p -> T (PatternTuple (Tuple p)) -> Decomposed T (Tuple p) Source #

(Flags flags, Decompose pa) => Decompose (Number flags pa) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

decompose :: Number flags pa -> T (PatternTuple (Number flags pa)) -> Decomposed T (Number flags pa) Source #

(Decompose pa, Decompose pb) => Decompose (pa, pb) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

decompose :: (pa, pb) -> T (PatternTuple (pa, pb)) -> Decomposed T (pa, pb) Source #

Decompose pa => Decompose (Tagged tag pa) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

decompose :: Tagged tag pa -> T (PatternTuple (Tagged tag pa)) -> Decomposed T (Tagged tag pa) Source #

(Decompose pa, Decompose pb, Decompose pc) => Decompose (pa, pb, pc) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

decompose :: (pa, pb, pc) -> T (PatternTuple (pa, pb, pc)) -> Decomposed T (pa, pb, pc) Source #

(Decompose pa, Decompose pb, Decompose pc, Decompose pd) => Decompose (pa, pb, pc, pd) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

decompose :: (pa, pb, pc, pd) -> T (PatternTuple (pa, pb, pc, pd)) -> Decomposed T (pa, pb, pc, pd) Source #

type family Decomposed (f :: * -> *) pattern Source #

Instances

Instances details
type Decomposed f () Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type Decomposed f () = ()
type Decomposed f (Complex pa) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type Decomposed f (Complex pa) = Complex (Decomposed f pa)
type Decomposed f (Atom a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type Decomposed f (Atom a) = f a
type Decomposed f (Tuple p) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type Decomposed f (Tuple p) = Tuple (Decomposed f p)
type Decomposed f (Number flags pa) Source # 
Instance details

Defined in LLVM.Extra.FastMath

type Decomposed f (Number flags pa) = Number flags (Decomposed f pa)
type Decomposed f (pa, pb) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type Decomposed f (pa, pb) = (Decomposed f pa, Decomposed f pb)
type Decomposed f (Tagged tag pa) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type Decomposed f (Tagged tag pa) = Tagged tag (Decomposed f pa)
type Decomposed f (pa, pb, pc) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type Decomposed f (pa, pb, pc) = (Decomposed f pa, Decomposed f pb, Decomposed f pc)
type Decomposed f (pa, pb, pc, pd) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type Decomposed f (pa, pb, pc, pd) = (Decomposed f pa, Decomposed f pb, Decomposed f pc, Decomposed f pd)

type family PatternTuple pattern Source #

Instances

Instances details
type PatternTuple () Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type PatternTuple () = ()
type PatternTuple (Complex pa) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type PatternTuple (Atom a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type PatternTuple (Atom a) = a
type PatternTuple (Tuple p) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type PatternTuple (Number flags pa) Source # 
Instance details

Defined in LLVM.Extra.FastMath

type PatternTuple (Number flags pa) = Number flags (PatternTuple pa)
type PatternTuple (pa, pb) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type PatternTuple (pa, pb) = (PatternTuple pa, PatternTuple pb)
type PatternTuple (Tagged tag pa) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type PatternTuple (Tagged tag pa) = Tagged tag (PatternTuple pa)
type PatternTuple (pa, pb, pc) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type PatternTuple (pa, pb, pc) = (PatternTuple pa, PatternTuple pb, PatternTuple pc)
type PatternTuple (pa, pb, pc, pd) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type PatternTuple (pa, pb, pc, pd) = (PatternTuple pa, PatternTuple pb, PatternTuple pc, PatternTuple pd)

modify :: (Compose a, Decompose pattern) => pattern -> (Decomposed T pattern -> a) -> T (PatternTuple pattern) -> T (Composed a) Source #

A combination of compose and decompose that let you operate on tuple multivalues as Haskell tuples.

modify2 :: (Compose a, Decompose patternA, Decompose patternB) => patternA -> patternB -> (Decomposed T patternA -> Decomposed T patternB -> a) -> T (PatternTuple patternA) -> T (PatternTuple patternB) -> T (Composed a) Source #

modifyF :: (Compose a, Decompose pattern, Functor f) => pattern -> (Decomposed T pattern -> f a) -> T (PatternTuple pattern) -> f (T (Composed a)) Source #

modifyF2 :: (Compose a, Decompose patternA, Decompose patternB, Functor f) => patternA -> patternB -> (Decomposed T patternA -> Decomposed T patternB -> f a) -> T (PatternTuple patternA) -> T (PatternTuple patternB) -> f (T (Composed a)) Source #

data Atom a Source #

Constructors

Atom 

Instances

Instances details
Decompose (Atom a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

decompose :: Atom a -> T (PatternTuple (Atom a)) -> Decomposed T (Atom a) Source #

type Decomposed f (Atom a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type Decomposed f (Atom a) = f a
type PatternTuple (Atom a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type PatternTuple (Atom a) = a

realPart :: T (Complex a) -> T a Source #

imagPart :: T (Complex a) -> T a Source #

lift1 :: (Repr a -> Repr b) -> T a -> T b Source #

liftM0 :: Monad m => m (Repr a) -> m (T a) Source #

liftM :: Monad m => (Repr a -> m (Repr b)) -> T a -> m (T b) Source #

liftM2 :: Monad m => (Repr a -> Repr b -> m (Repr c)) -> T a -> T b -> m (T c) Source #

liftM3 :: Monad m => (Repr a -> Repr b -> Repr c -> m (Repr d)) -> T a -> T b -> T c -> m (T d) Source #

class C a => IntegerConstant a where Source #

Methods

fromInteger' :: Integer -> T a Source #

Instances

Instances details
IntegerConstant Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

IntegerConstant Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

IntegerConstant Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

IntegerConstant Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

IntegerConstant Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

IntegerConstant Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

IntegerConstant Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

IntegerConstant Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

IntegerConstant Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

IntegerConstant Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

IntegerConstant Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

IntegerConstant Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Positive n => IntegerConstant (IntN n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

fromInteger' :: Integer -> T (IntN n) Source #

Positive n => IntegerConstant (WordN n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

fromInteger' :: Integer -> T (WordN n) Source #

(Flags flags, MultiValue a, IntegerConstant a) => IntegerConstant (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

fromInteger' :: Integer -> T (Number flags a) Source #

(Positive n, IntegerConstant a) => IntegerConstant (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector.Instance

Methods

fromInteger' :: Integer -> T (Vector n a) Source #

IntegerConstant a => IntegerConstant (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

fromInteger' :: Integer -> T (Tagged tag a) Source #

class IntegerConstant a => RationalConstant a where Source #

Instances

Instances details
RationalConstant Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

RationalConstant Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

(Flags flags, MultiValue a, RationalConstant a) => RationalConstant (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

fromRational' :: Rational -> T (Number flags a) Source #

(Positive n, RationalConstant a) => RationalConstant (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector.Instance

Methods

fromRational' :: Rational -> T (Vector n a) Source #

RationalConstant a => RationalConstant (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

fromRational' :: Rational -> T (Tagged tag a) Source #

class C a => Additive a where Source #

Methods

add :: T a -> T a -> CodeGenFunction r (T a) Source #

sub :: T a -> T a -> CodeGenFunction r (T a) Source #

neg :: T a -> CodeGenFunction r (T a) Source #

Instances

Instances details
Additive Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Additive Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Additive Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Additive Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Additive Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Additive Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Additive Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Additive Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Additive Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Additive Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Additive Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Additive Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Positive n => Additive (IntN n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

add :: T (IntN n) -> T (IntN n) -> CodeGenFunction r (T (IntN n)) Source #

sub :: T (IntN n) -> T (IntN n) -> CodeGenFunction r (T (IntN n)) Source #

neg :: T (IntN n) -> CodeGenFunction r (T (IntN n)) Source #

Positive n => Additive (WordN n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

add :: T (WordN n) -> T (WordN n) -> CodeGenFunction r (T (WordN n)) Source #

sub :: T (WordN n) -> T (WordN n) -> CodeGenFunction r (T (WordN n)) Source #

neg :: T (WordN n) -> CodeGenFunction r (T (WordN n)) Source #

(Flags flags, MultiValue a, Additive a) => Additive (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

add :: T (Number flags a) -> T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

sub :: T (Number flags a) -> T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

neg :: T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

(Positive n, Additive a) => Additive (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector.Instance

Methods

add :: T (Vector n a) -> T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

sub :: T (Vector n a) -> T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

neg :: T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

Additive a => Additive (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

add :: T (Tagged tag a) -> T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

sub :: T (Tagged tag a) -> T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

neg :: T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

class Additive a => PseudoRing a where Source #

Methods

mul :: T a -> T a -> CodeGenFunction r (T a) Source #

Instances

Instances details
PseudoRing Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

mul :: T Int16 -> T Int16 -> CodeGenFunction r (T Int16) Source #

PseudoRing Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

mul :: T Int32 -> T Int32 -> CodeGenFunction r (T Int32) Source #

PseudoRing Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

mul :: T Int64 -> T Int64 -> CodeGenFunction r (T Int64) Source #

PseudoRing Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

mul :: T Int8 -> T Int8 -> CodeGenFunction r (T Int8) Source #

PseudoRing Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

PseudoRing Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

PseudoRing Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

PseudoRing Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

mul :: T Word8 -> T Word8 -> CodeGenFunction r (T Word8) Source #

PseudoRing Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

PseudoRing Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

mul :: T Float -> T Float -> CodeGenFunction r (T Float) Source #

PseudoRing Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

mul :: T Int -> T Int -> CodeGenFunction r (T Int) Source #

PseudoRing Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

mul :: T Word -> T Word -> CodeGenFunction r (T Word) Source #

(Flags flags, MultiValue a, PseudoRing a) => PseudoRing (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

mul :: T (Number flags a) -> T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

(Positive n, PseudoRing a) => PseudoRing (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector.Instance

Methods

mul :: T (Vector n a) -> T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

PseudoRing a => PseudoRing (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

mul :: T (Tagged tag a) -> T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

class PseudoRing a => Field a where Source #

Methods

fdiv :: T a -> T a -> CodeGenFunction r (T a) Source #

Instances

Instances details
Field Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Field Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

(Flags flags, MultiValue a, Field a) => Field (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

fdiv :: T (Number flags a) -> T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

Field a => Field (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

fdiv :: T (Tagged tag a) -> T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

type family Scalar vector Source #

Instances

Instances details
type Scalar Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type Scalar Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type Scalar (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

type Scalar (Number flags a) = Number flags (Scalar a)
type Scalar (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type Scalar (Tagged tag a) = Tagged tag (Scalar a)

class (PseudoRing (Scalar v), Additive v) => PseudoModule v where Source #

Methods

scale :: T (Scalar v) -> T v -> CodeGenFunction r (T v) Source #

Instances

Instances details
PseudoModule Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

PseudoModule Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

(Flags flags, MultiValue a, a ~ Scalar v, MultiValue v, PseudoModule v) => PseudoModule (Number flags v) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

scale :: T (Scalar (Number flags v)) -> T (Number flags v) -> CodeGenFunction r (T (Number flags v)) Source #

PseudoModule a => PseudoModule (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

scale :: T (Scalar (Tagged tag a)) -> T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

class Additive a => Real a where Source #

Methods

min :: T a -> T a -> CodeGenFunction r (T a) Source #

max :: T a -> T a -> CodeGenFunction r (T a) Source #

abs :: T a -> CodeGenFunction r (T a) Source #

signum :: T a -> CodeGenFunction r (T a) Source #

Instances

Instances details
Real Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Real Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Real Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Real Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Real Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Real Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Real Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Real Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Real Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Real Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Real Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Real Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Positive n => Real (IntN n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

min :: T (IntN n) -> T (IntN n) -> CodeGenFunction r (T (IntN n)) Source #

max :: T (IntN n) -> T (IntN n) -> CodeGenFunction r (T (IntN n)) Source #

abs :: T (IntN n) -> CodeGenFunction r (T (IntN n)) Source #

signum :: T (IntN n) -> CodeGenFunction r (T (IntN n)) Source #

Positive n => Real (WordN n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

min :: T (WordN n) -> T (WordN n) -> CodeGenFunction r (T (WordN n)) Source #

max :: T (WordN n) -> T (WordN n) -> CodeGenFunction r (T (WordN n)) Source #

abs :: T (WordN n) -> CodeGenFunction r (T (WordN n)) Source #

signum :: T (WordN n) -> CodeGenFunction r (T (WordN n)) Source #

(Flags flags, MultiValue a, Real a) => Real (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

min :: T (Number flags a) -> T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

max :: T (Number flags a) -> T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

abs :: T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

signum :: T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

(Positive n, Real a) => Real (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector.Instance

Methods

min :: T (Vector n a) -> T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

max :: T (Vector n a) -> T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

abs :: T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

signum :: T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

Real a => Real (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

min :: T (Tagged tag a) -> T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

max :: T (Tagged tag a) -> T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

abs :: T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

signum :: T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

class Real a => Fraction a where Source #

Methods

truncate :: T a -> CodeGenFunction r (T a) Source #

fraction :: T a -> CodeGenFunction r (T a) Source #

Instances

Instances details
Fraction Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Fraction Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

(Flags flags, MultiValue a, Fraction a) => Fraction (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

truncate :: T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

fraction :: T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

(Positive n, Fraction a) => Fraction (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector.Instance

Methods

truncate :: T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

fraction :: T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

Fraction a => Fraction (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

truncate :: T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

fraction :: T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

class (Repr i ~ Value ir, IsInteger ir, IntegerConstant ir, CmpRet ir, IsPrimitive ir) => NativeInteger i ir Source #

class (Repr a ~ Value ar, IsFloating ar, RationalConstant ar, CmpRet ar, IsPrimitive ar) => NativeFloating a ar Source #

Instances

Instances details
NativeFloating Double Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

NativeFloating Float Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

class Field a => Algebraic a where Source #

Methods

sqrt :: T a -> CodeGenFunction r (T a) Source #

Instances

Instances details
Algebraic Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Algebraic Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

(Flags flags, MultiValue a, Algebraic a) => Algebraic (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

sqrt :: T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

Algebraic a => Algebraic (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

sqrt :: T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

class Algebraic a => Transcendental a where Source #

Methods

pi :: CodeGenFunction r (T a) Source #

sin :: T a -> CodeGenFunction r (T a) Source #

cos :: T a -> CodeGenFunction r (T a) Source #

exp :: T a -> CodeGenFunction r (T a) Source #

log :: T a -> CodeGenFunction r (T a) Source #

pow :: T a -> T a -> CodeGenFunction r (T a) Source #

Instances

Instances details
Transcendental Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Transcendental Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

(Flags flags, MultiValue a, Transcendental a) => Transcendental (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

pi :: CodeGenFunction r (T (Number flags a)) Source #

sin :: T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

cos :: T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

exp :: T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

log :: T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

pow :: T (Number flags a) -> T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

Transcendental a => Transcendental (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

pi :: CodeGenFunction r (T (Tagged tag a)) Source #

sin :: T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

cos :: T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

exp :: T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

log :: T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

pow :: T (Tagged tag a) -> T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

class C a => Select a where Source #

Methods

select :: T Bool -> T a -> T a -> CodeGenFunction r (T a) Source #

Instances

Instances details
Select Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

select :: T Bool -> T Int16 -> T Int16 -> CodeGenFunction r (T Int16) Source #

Select Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

select :: T Bool -> T Int32 -> T Int32 -> CodeGenFunction r (T Int32) Source #

Select Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

select :: T Bool -> T Int64 -> T Int64 -> CodeGenFunction r (T Int64) Source #

Select Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

select :: T Bool -> T Int8 -> T Int8 -> CodeGenFunction r (T Int8) Source #

Select Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Select Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Select Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Select Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

select :: T Bool -> T Word8 -> T Word8 -> CodeGenFunction r (T Word8) Source #

Select Bool8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

select :: T Bool -> T Bool8 -> T Bool8 -> CodeGenFunction r (T Bool8) Source #

Select Bool Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

select :: T Bool -> T Bool -> T Bool -> CodeGenFunction r (T Bool) Source #

Select Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Select Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

select :: T Bool -> T Float -> T Float -> CodeGenFunction r (T Float) Source #

Select Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

select :: T Bool -> T Int -> T Int -> CodeGenFunction r (T Int) Source #

Select Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

select :: T Bool -> T Word -> T Word -> CodeGenFunction r (T Word) Source #

(Flags flags, MultiValue a, Select a) => Select (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

select :: T Bool -> T (Number flags a) -> T (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

(Select a, Select b) => Select (a, b) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

select :: T Bool -> T (a, b) -> T (a, b) -> CodeGenFunction r (T (a, b)) Source #

Select a => Select (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

select :: T Bool -> T (Tagged tag a) -> T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

(Select a, Select b, Select c) => Select (a, b, c) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

select :: T Bool -> T (a, b, c) -> T (a, b, c) -> CodeGenFunction r (T (a, b, c)) Source #

class Real a => Comparison a where Source #

Methods

cmp :: CmpPredicate -> T a -> T a -> CodeGenFunction r (T Bool) Source #

It must hold

max x y  ==  do gt <- cmp CmpGT x y; select gt x y

Instances

Instances details
Comparison Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Comparison Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Comparison Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Comparison Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Comparison Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Comparison Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Comparison Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Comparison Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Comparison Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Comparison Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Comparison Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Comparison Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Positive n => Comparison (IntN n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

cmp :: CmpPredicate -> T (IntN n) -> T (IntN n) -> CodeGenFunction r (T Bool) Source #

Positive n => Comparison (WordN n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

cmp :: CmpPredicate -> T (WordN n) -> T (WordN n) -> CodeGenFunction r (T Bool) Source #

(Flags flags, MultiValue a, Comparison a) => Comparison (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

cmp :: CmpPredicate -> T (Number flags a) -> T (Number flags a) -> CodeGenFunction r (T Bool) Source #

Comparison a => Comparison (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

cmp :: CmpPredicate -> T (Tagged tag a) -> T (Tagged tag a) -> CodeGenFunction r (T Bool) Source #

class Comparison a => FloatingComparison a where Source #

Methods

fcmp :: FPPredicate -> T a -> T a -> CodeGenFunction r (T Bool) Source #

Instances

Instances details
FloatingComparison Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

(Flags flags, MultiValue a, FloatingComparison a) => FloatingComparison (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

fcmp :: FPPredicate -> T (Number flags a) -> T (Number flags a) -> CodeGenFunction r (T Bool) Source #

FloatingComparison a => FloatingComparison (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

fcmp :: FPPredicate -> T (Tagged tag a) -> T (Tagged tag a) -> CodeGenFunction r (T Bool) Source #

class C a => Logic a where Source #

Methods

and :: T a -> T a -> CodeGenFunction r (T a) Source #

or :: T a -> T a -> CodeGenFunction r (T a) Source #

xor :: T a -> T a -> CodeGenFunction r (T a) Source #

inv :: T a -> CodeGenFunction r (T a) Source #

Instances

Instances details
Logic Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Logic Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Logic Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Logic Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Logic Bool8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Logic Bool Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Positive n => Logic (WordN n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

and :: T (WordN n) -> T (WordN n) -> CodeGenFunction r (T (WordN n)) Source #

or :: T (WordN n) -> T (WordN n) -> CodeGenFunction r (T (WordN n)) Source #

xor :: T (WordN n) -> T (WordN n) -> CodeGenFunction r (T (WordN n)) Source #

inv :: T (WordN n) -> CodeGenFunction r (T (WordN n)) Source #

(IsInteger w, IsConst w) => Logic (T w i) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

and :: T0 (T w i) -> T0 (T w i) -> CodeGenFunction r (T0 (T w i)) Source #

or :: T0 (T w i) -> T0 (T w i) -> CodeGenFunction r (T0 (T w i)) Source #

xor :: T0 (T w i) -> T0 (T w i) -> CodeGenFunction r (T0 (T w i)) Source #

inv :: T0 (T w i) -> CodeGenFunction r (T0 (T w i)) Source #

(Positive n, Logic a) => Logic (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector.Instance

Methods

and :: T (Vector n a) -> T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

or :: T (Vector n a) -> T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

xor :: T (Vector n a) -> T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

inv :: T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

Logic a => Logic (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

and :: T (Tagged tag a) -> T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

or :: T (Tagged tag a) -> T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

xor :: T (Tagged tag a) -> T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

inv :: T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

class BitShift a where Source #

Methods

shl :: T a -> T a -> CodeGenFunction r (T a) Source #

shr :: T a -> T a -> CodeGenFunction r (T a) Source #

Instances

Instances details
BitShift Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

BitShift Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

BitShift Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

BitShift Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

BitShift Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

BitShift Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

BitShift Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

BitShift Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

BitShift Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

shl :: T Int -> T Int -> CodeGenFunction r (T Int) Source #

shr :: T Int -> T Int -> CodeGenFunction r (T Int) Source #

BitShift Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

(Positive n, BitShift a) => BitShift (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector.Instance

Methods

shl :: T (Vector n a) -> T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

shr :: T (Vector n a) -> T (Vector n a) -> CodeGenFunction r (T (Vector n a)) Source #

class PseudoRing a => Integral a where Source #

Methods

idiv :: T a -> T a -> CodeGenFunction r (T a) Source #

irem :: T a -> T a -> CodeGenFunction r (T a) Source #

Instances

Instances details
Integral Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Integral Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Integral Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Integral Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Integral Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

idiv :: T Int -> T Int -> CodeGenFunction r (T Int) Source #

irem :: T Int -> T Int -> CodeGenFunction r (T Int) Source #

Integral Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Integral a => Integral (Tagged tag a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

idiv :: T (Tagged tag a) -> T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

irem :: T (Tagged tag a) -> T (Tagged tag a) -> CodeGenFunction r (T (Tagged tag a)) Source #

newtype Array n a Source #

Constructors

Array [a] 

Instances

Instances details
Integer n => Foldable (Array n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Array

Methods

fold :: Monoid m => Array n m -> m #

foldMap :: Monoid m => (a -> m) -> Array n a -> m #

foldMap' :: Monoid m => (a -> m) -> Array n a -> m #

foldr :: (a -> b -> b) -> b -> Array n a -> b #

foldr' :: (a -> b -> b) -> b -> Array n a -> b #

foldl :: (b -> a -> b) -> b -> Array n a -> b #

foldl' :: (b -> a -> b) -> b -> Array n a -> b #

foldr1 :: (a -> a -> a) -> Array n a -> a #

foldl1 :: (a -> a -> a) -> Array n a -> a #

toList :: Array n a -> [a] #

null :: Array n a -> Bool #

length :: Array n a -> Int #

elem :: Eq a => a -> Array n a -> Bool #

maximum :: Ord a => Array n a -> a #

minimum :: Ord a => Array n a -> a #

sum :: Num a => Array n a -> a #

product :: Num a => Array n a -> a #

Integer n => Traversable (Array n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Array

Methods

traverse :: Applicative f => (a -> f b) -> Array n a -> f (Array n b) #

sequenceA :: Applicative f => Array n (f a) -> f (Array n a) #

mapM :: Monad m => (a -> m b) -> Array n a -> m (Array n b) #

sequence :: Monad m => Array n (m a) -> m (Array n a) #

Integer n => Applicative (Array n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Array

Methods

pure :: a -> Array n a #

(<*>) :: Array n (a -> b) -> Array n a -> Array n b #

liftA2 :: (a -> b -> c) -> Array n a -> Array n b -> Array n c #

(*>) :: Array n a -> Array n b -> Array n b #

(<*) :: Array n a -> Array n b -> Array n a #

Integer n => Functor (Array n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Array

Methods

fmap :: (a -> b) -> Array n a -> Array n b #

(<$) :: a -> Array n b -> Array n a #

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

Defined in LLVM.Extra.Multi.Value.Array

Methods

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

show :: Array n a -> String #

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

Eq a => Eq (Array n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Array

Methods

(==) :: Array n a -> Array n a -> Bool #

(/=) :: Array n a -> Array n a -> Bool #

(Natural n, C a, Natural (n :*: SizeOf (Struct a))) => C (Array n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Array

Methods

pack :: Array n a -> Struct (Array n a) Source #

unpack :: Struct (Array n a) -> Array n a Source #

(Natural n, C a) => C (Array n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Array

Associated Types

type Repr (Array n a) Source #

Methods

cons :: Array n a -> T (Array n a) Source #

undef :: T (Array n a) Source #

zero :: T (Array n a) Source #

phi :: BasicBlock -> T (Array n a) -> CodeGenFunction r (T (Array n a)) Source #

addPhi :: BasicBlock -> T (Array n a) -> T (Array n a) -> CodeGenFunction r () Source #

type Repr (Array n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Array

type Repr (Array n a) = Value (Array n (Struct a))

withArraySize :: (Proxy n -> gen (Array n a)) -> gen (Array n a) Source #

extractArrayValue :: (Natural n, ArrayIndex n i, C a) => i -> T (Array n a) -> CodeGenFunction r (T a) Source #

insertArrayValue :: (Natural n, ArrayIndex n i, C a) => i -> T a -> T (Array n a) -> CodeGenFunction r (T (Array n a)) Source #