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

LLVM.Extra.Multi.Value.Vector

Documentation

cons :: (Positive n, C a) => Vector n a -> MVVector n a Source #

fst :: MVVector n (a, b) -> MVVector n a Source #

snd :: MVVector n (a, b) -> MVVector n b Source #

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

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

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

zip :: MVVector n a -> MVVector n b -> MVVector n (a, b) Source #

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

unzip :: MVVector n (a, b) -> (MVVector n a, MVVector n b) Source #

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

swap :: MVVector n (a, b) -> MVVector n (b, a) Source #

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

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

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

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

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

insert :: (Positive n, C a) => Value Word32 -> T a -> MVVector n a -> CodeGenFunction r (MVVector n a) Source #

replicate :: (Positive n, C a) => T a -> CodeGenFunction r (MVVector n a) Source #

iterate :: (Positive n, C a) => (T a -> CodeGenFunction r (T a)) -> T a -> CodeGenFunction r (MVVector n a) Source #

dissect :: (Positive n, C a) => MVVector n a -> CodeGenFunction r [T a] Source #

dissect1 :: (Positive n, C a) => MVVector n a -> CodeGenFunction r (T [] (T a)) Source #

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

Instances

Instances details
NativeInteger Int16 Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Vector

NativeInteger Int32 Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Vector

NativeInteger Int64 Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Vector

NativeInteger Int8 Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Vector

NativeInteger Word16 Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Vector

NativeInteger Word32 Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Vector

NativeInteger Word64 Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Vector

NativeInteger Word8 Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Vector

NativeInteger Int Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Vector

NativeInteger Word Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Vector

(Positive n, n ~ m, NativeInteger n i ir, NativeInteger i ir) => NativeInteger (Vector n i) (Vector m ir) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Vector

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

Instances

Instances details
NativeFloating Double Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Vector

NativeFloating Float Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Vector

(Positive n, n ~ m, NativeFloating n a ar, NativeFloating a ar) => NativeFloating (Vector n a) (Vector m ar) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Vector

fromIntegral :: (NativeInteger i ir, NativeFloating a ar, ShapeOf ir ~ ShapeOf ar) => T i -> CodeGenFunction r (T a) Source #

truncateToInt :: (NativeInteger i ir, NativeFloating a ar, ShapeOf ir ~ ShapeOf ar) => T a -> CodeGenFunction r (T i) Source #

splitFractionToInt :: (NativeInteger i ir, NativeFloating a ar, ShapeOf ir ~ ShapeOf ar) => T a -> CodeGenFunction r (T (i, a)) Source #