Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
LLVM.Extra.Nice.Value
Synopsis
- newtype T a = Cons (Repr a)
- class C a where
- type Repr a
- cons :: a -> T a
- undef :: T a
- zero :: T a
- phi :: BasicBlock -> T a -> CodeGenFunction r (T a)
- addPhi :: BasicBlock -> T a -> T a -> CodeGenFunction r ()
- cast :: Repr a ~ Repr b => T a -> T b
- consPrimitive :: (IsConst al, Value al ~ Repr a) => al -> T a
- undefPrimitive :: (IsType al, Value al ~ Repr a) => T a
- zeroPrimitive :: (IsType al, Value al ~ Repr a) => T a
- phiPrimitive :: (IsFirstClass al, Value al ~ Repr a) => BasicBlock -> T a -> CodeGenFunction r (T a)
- addPhiPrimitive :: (IsFirstClass al, Value al ~ Repr a) => BasicBlock -> T a -> T a -> CodeGenFunction r ()
- consTuple :: (Value a, Repr a ~ ValueOf a) => a -> T a
- undefTuple :: (Repr a ~ al, Undefined al) => T a
- zeroTuple :: (Repr a ~ al, Zero al) => T a
- phiTuple :: (Repr a ~ al, Phi al) => BasicBlock -> T a -> CodeGenFunction r (T a)
- addPhiTuple :: (Repr a ~ al, Phi al) => BasicBlock -> T a -> T a -> CodeGenFunction r ()
- consUnit :: Repr a ~ () => a -> T a
- undefUnit :: Repr a ~ () => T a
- zeroUnit :: Repr a ~ () => T a
- phiUnit :: Repr a ~ () => BasicBlock -> T a -> CodeGenFunction r (T a)
- addPhiUnit :: Repr a ~ () => BasicBlock -> T a -> T a -> CodeGenFunction r ()
- boolPFrom8 :: T Bool8 -> T Bool
- bool8FromP :: T Bool -> T Bool8
- intFromBool8 :: NativeInteger i ir => T Bool8 -> CodeGenFunction r (T i)
- floatFromBool8 :: NativeFloating a ar => T Bool8 -> CodeGenFunction r (T a)
- toEnum :: Repr w ~ Value w => T w -> T (T w e)
- fromEnum :: Repr w ~ Value w => T (T w e) -> T w
- succ :: (IsArithmetic w, IntegerConstant w) => T (T w e) -> CodeGenFunction r (T (T w e))
- pred :: (IsArithmetic w, IntegerConstant w) => T (T w e) -> CodeGenFunction r (T (T w e))
- cmpEnum :: (CmpRet w, IsPrimitive w) => CmpPredicate -> T (T w a) -> T (T w a) -> CodeGenFunction r (T Bool)
- class C a => Bounded a where
- splitMaybe :: T (Maybe a) -> (T Bool, T a)
- toMaybe :: T Bool -> T a -> T (Maybe a)
- nothing :: C a => T (Maybe a)
- just :: T a -> T (Maybe a)
- fst :: T (a, b) -> T a
- snd :: T (a, b) -> T b
- curry :: (T (a, b) -> c) -> T a -> T b -> c
- uncurry :: (T a -> T b -> c) -> T (a, b) -> c
- mapFst :: (T a0 -> T a1) -> T (a0, b) -> T (a1, b)
- mapSnd :: (T b0 -> T b1) -> T (a, b0) -> T (a, b1)
- mapFstF :: Functor f => (T a0 -> f (T a1)) -> T (a0, b) -> f (T (a1, b))
- mapSndF :: Functor f => (T b0 -> f (T b1)) -> T (a, b0) -> f (T (a, b1))
- swap :: T (a, b) -> T (b, a)
- fst3 :: T (a, b, c) -> T a
- snd3 :: T (a, b, c) -> T b
- thd3 :: T (a, b, c) -> T c
- curry3 :: (T (a, b, c) -> d) -> T a -> T b -> T c -> d
- uncurry3 :: (T a -> T b -> T c -> d) -> T (a, b, c) -> d
- mapFst3 :: (T a0 -> T a1) -> T (a0, b, c) -> T (a1, b, c)
- mapSnd3 :: (T b0 -> T b1) -> T (a, b0, c) -> T (a, b1, c)
- mapThd3 :: (T c0 -> T c1) -> T (a, b, c0) -> T (a, b, c1)
- mapFst3F :: Functor f => (T a0 -> f (T a1)) -> T (a0, b, c) -> f (T (a1, b, c))
- mapSnd3F :: Functor f => (T b0 -> f (T b1)) -> T (a, b0, c) -> f (T (a, b1, c))
- mapThd3F :: Functor f => (T c0 -> f (T c1)) -> T (a, b, c0) -> f (T (a, b, c1))
- zip :: T a -> T b -> T (a, b)
- zip3 :: T a -> T b -> T c -> T (a, b, c)
- zip4 :: T a -> T b -> T c -> T d -> T (a, b, c, d)
- unzip :: T (a, b) -> (T a, T b)
- unzip3 :: T (a, b, c) -> (T a, T b, T c)
- unzip4 :: T (a, b, c, d) -> (T a, T b, T c, T d)
- tuple :: T tuple -> T (Tuple tuple)
- untuple :: T (Tuple tuple) -> T tuple
- class Struct struct where
- consStruct :: T struct ~ a => a -> T a
- undefStruct :: T struct ~ a => T a
- zeroStruct :: T struct ~ a => T a
- phiStruct :: T struct ~ a => BasicBlock -> T a -> CodeGenFunction r (T a)
- addPhiStruct :: T struct ~ a => BasicBlock -> T a -> T a -> CodeGenFunction r ()
- structCons :: T a -> T (T as) -> T (T (a, as))
- structUncons :: T (T (a, as)) -> (T a, T (T as))
- tag :: T a -> T (Tagged tag a)
- untag :: T (Tagged tag a) -> T a
- liftTaggedM :: Monad m => (T a -> m (T b)) -> T (Tagged tag a) -> m (T (Tagged tag b))
- liftTaggedM2 :: Monad m => (T a -> T b -> m (T c)) -> T (Tagged tag a) -> T (Tagged tag b) -> m (T (Tagged tag c))
- consComplex :: T a -> T a -> T (Complex a)
- deconsComplex :: T (Complex a) -> (T a, T a)
- class Compose nicetuple where
- class Composed (Decomposed T pattern) ~ PatternTuple pattern => Decompose pattern where
- decompose :: pattern -> T (PatternTuple pattern) -> Decomposed T pattern
- type family Decomposed (f :: * -> *) pattern
- type family PatternTuple pattern
- modify :: (Compose a, Decompose pattern) => pattern -> (Decomposed T pattern -> a) -> T (PatternTuple pattern) -> T (Composed a)
- 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)
- modifyF :: (Compose a, Decompose pattern, Functor f) => pattern -> (Decomposed T pattern -> f a) -> T (PatternTuple pattern) -> f (T (Composed a))
- 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))
- data Atom a = Atom
- atom :: Atom a
- realPart :: T (Complex a) -> T a
- imagPart :: T (Complex a) -> T a
- lift1 :: (Repr a -> Repr b) -> T a -> T b
- liftM0 :: Monad m => m (Repr a) -> m (T a)
- liftM :: Monad m => (Repr a -> m (Repr b)) -> T a -> m (T b)
- liftM2 :: Monad m => (Repr a -> Repr b -> m (Repr c)) -> T a -> T b -> m (T c)
- liftM3 :: Monad m => (Repr a -> Repr b -> Repr c -> m (Repr d)) -> T a -> T b -> T c -> m (T d)
- class C a => IntegerConstant a where
- fromInteger' :: Integer -> T a
- class IntegerConstant a => RationalConstant a where
- fromRational' :: Rational -> T a
- class C a => Additive a where
- add :: T a -> T a -> CodeGenFunction r (T a)
- sub :: T a -> T a -> CodeGenFunction r (T a)
- neg :: T a -> CodeGenFunction r (T a)
- inc :: (Additive i, IntegerConstant i) => T i -> CodeGenFunction r (T i)
- dec :: (Additive i, IntegerConstant i) => T i -> CodeGenFunction r (T i)
- class Additive a => PseudoRing a where
- mul :: T a -> T a -> CodeGenFunction r (T a)
- class PseudoRing a => Field a where
- fdiv :: T a -> T a -> CodeGenFunction r (T a)
- type family Scalar vector
- class (PseudoRing (Scalar v), Additive v) => PseudoModule v where
- class Additive a => Real a where
- min :: T a -> T a -> CodeGenFunction r (T a)
- max :: T a -> T a -> CodeGenFunction r (T a)
- abs :: T a -> CodeGenFunction r (T a)
- signum :: T a -> CodeGenFunction r (T a)
- class Real a => Fraction a where
- truncate :: T a -> CodeGenFunction r (T a)
- fraction :: T a -> CodeGenFunction r (T a)
- class (Repr i ~ Value ir, IsInteger ir, IntegerConstant ir, CmpRet ir, IsPrimitive ir) => NativeInteger i ir
- class (Repr a ~ Value ar, IsFloating ar, RationalConstant ar, CmpRet ar, IsPrimitive ar) => NativeFloating a ar
- truncateToInt :: (NativeInteger i ir, NativeFloating a ar) => T a -> CodeGenFunction r (T i)
- floorToInt :: (NativeInteger i ir, NativeFloating a ar) => T a -> CodeGenFunction r (T i)
- ceilingToInt :: (NativeInteger i ir, NativeFloating a ar) => T a -> CodeGenFunction r (T i)
- roundToIntFast :: (NativeInteger i ir, NativeFloating a ar) => T a -> CodeGenFunction r (T i)
- splitFractionToInt :: (NativeInteger i ir, NativeFloating a ar) => T a -> CodeGenFunction r (T (i, a))
- class Field a => Algebraic a where
- sqrt :: T a -> CodeGenFunction r (T a)
- class Algebraic a => Transcendental a where
- pi :: CodeGenFunction r (T a)
- sin, cos, exp, log :: T a -> CodeGenFunction r (T a)
- pow :: T a -> T a -> CodeGenFunction r (T a)
- class C a => Select a where
- class Real a => Comparison a where
- cmp :: CmpPredicate -> T a -> T a -> CodeGenFunction r (T Bool)
- class Comparison a => FloatingComparison a where
- fcmp :: FPPredicate -> T a -> T a -> CodeGenFunction r (T Bool)
- class C a => Logic a where
- and :: T a -> T a -> CodeGenFunction r (T a)
- or :: T a -> T a -> CodeGenFunction r (T a)
- xor :: T a -> T a -> CodeGenFunction r (T a)
- inv :: T a -> CodeGenFunction r (T a)
- class BitShift a where
- shl :: T a -> T a -> CodeGenFunction r (T a)
- shr :: T a -> T a -> CodeGenFunction r (T a)
- class PseudoRing a => Integral a where
- idiv :: T a -> T a -> CodeGenFunction r (T a)
- irem :: T a -> T a -> CodeGenFunction r (T a)
- fromIntegral :: (NativeInteger i ir, NativeFloating a ar) => T i -> CodeGenFunction r (T a)
- newtype Array n a = Array [a]
- withArraySize :: (Proxy n -> gen (Array n a)) -> gen (Array n a)
- extractArrayValue :: (Natural n, ArrayIndex n i, C a) => i -> T (Array n a) -> CodeGenFunction r (T a)
- insertArrayValue :: (Natural n, ArrayIndex n i, C a) => i -> T a -> T (Array n a) -> CodeGenFunction r (T (Array n a))
Documentation
Instances
Methods
phi :: BasicBlock -> T a -> CodeGenFunction r (T a) Source #
addPhi :: BasicBlock -> T a -> T a -> CodeGenFunction r () Source #
Instances
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 #
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 #
phiUnit :: Repr a ~ () => BasicBlock -> T a -> CodeGenFunction r (T a) Source #
addPhiUnit :: Repr a ~ () => BasicBlock -> T a -> T a -> CodeGenFunction r () Source #
intFromBool8 :: NativeInteger i ir => T Bool8 -> CodeGenFunction r (T i) Source #
floatFromBool8 :: NativeFloating a ar => T Bool8 -> CodeGenFunction r (T a) 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 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
Struct () Source # | |
Defined in LLVM.Extra.Nice.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 # | |
Defined in LLVM.Extra.Nice.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 # |
liftTaggedM2 :: Monad m => (T a -> T b -> m (T c)) -> T (Tagged tag a) -> T (Tagged tag b) -> m (T (Tagged tag c)) Source #
class Compose nicetuple where Source #
Instances
Compose () Source # | |
Compose a => Compose (Complex a) Source # | |
Compose (T a) Source # | |
Compose tuple => Compose (Tuple tuple) Source # | |
(Flags flags, Compose a) => Compose (Number flags a) Source # | |
(Compose a, Compose b) => Compose (a, b) Source # | |
Compose a => Compose (Tagged tag a) Source # | |
(Compose a, Compose b, Compose c) => Compose (a, b, c) Source # | |
(Compose a, Compose b, Compose c, Compose d) => Compose (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 :: NiceValue ((a,b),(c,d)) -> ((NiceValue a, NiceValue b), NiceValue (c,d)) f = decompose ((atom,atom),atom)
Instances
type family Decomposed (f :: * -> *) pattern Source #
Instances
type Decomposed f () Source # | |
Defined in LLVM.Extra.Nice.Value.Private type Decomposed f () = () | |
type Decomposed f (Complex pa) Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
type Decomposed f (Atom a) Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
type Decomposed f (Tuple p) Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
type Decomposed f (Number flags pa) Source # | |
Defined in LLVM.Extra.FastMath | |
type Decomposed f (pa, pb) Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
type Decomposed f (Tagged tag pa) Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
type Decomposed f (pa, pb, pc) Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
type Decomposed f (pa, pb, pc, pd) Source # | |
Defined in LLVM.Extra.Nice.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
type PatternTuple () Source # | |
Defined in LLVM.Extra.Nice.Value.Private type PatternTuple () = () | |
type PatternTuple (Complex pa) Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
type PatternTuple (Atom a) Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
type PatternTuple (Tuple p) Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
type PatternTuple (Number flags pa) Source # | |
Defined in LLVM.Extra.FastMath | |
type PatternTuple (pa, pb) Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
type PatternTuple (Tagged tag pa) Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
type PatternTuple (pa, pb, pc) Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
type PatternTuple (pa, pb, pc, pd) Source # | |
Defined in LLVM.Extra.Nice.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 #
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 #
Constructors
Atom |
Instances
Decompose (Atom a) Source # | |
Defined in LLVM.Extra.Nice.Value.Private Methods decompose :: Atom a -> T (PatternTuple (Atom a)) -> Decomposed T (Atom a) Source # | |
type Decomposed f (Atom a) Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
type PatternTuple (Atom a) Source # | |
Defined in LLVM.Extra.Nice.Value.Private |
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
class IntegerConstant a => RationalConstant a where Source #
Methods
fromRational' :: Rational -> T a Source #
Instances
RationalConstant Double Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
RationalConstant Float Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
(Flags flags, NiceValue a, RationalConstant a) => RationalConstant (Number flags a) Source # | |
Defined in LLVM.Extra.FastMath | |
(Positive n, RationalConstant a) => RationalConstant (Vector n a) Source # | |
Defined in LLVM.Extra.Nice.Vector.Instance Methods fromRational' :: Rational -> T (Vector n a) Source # | |
RationalConstant a => RationalConstant (Tagged tag a) Source # | |
Defined in LLVM.Extra.Nice.Value.Private |
class C a => Additive a where Source #
Methods
add :: T a -> T a -> CodeGenFunction r (T a) Source #
Instances
Additive Int16 Source # | |
Additive Int32 Source # | |
Additive Int64 Source # | |
Additive Int8 Source # | |
Additive Word16 Source # | |
Additive Word32 Source # | |
Additive Word64 Source # | |
Additive Word8 Source # | |
Additive Double Source # | |
Additive Float Source # | |
Additive Int Source # | |
Additive Word Source # | |
Positive n => Additive (IntN n) Source # | |
Positive n => Additive (WordN n) Source # | |
(Flags flags, NiceValue a, Additive a) => Additive (Number flags a) Source # | |
Defined in LLVM.Extra.FastMath | |
(Positive n, Additive a) => Additive (Vector n a) Source # | |
Additive a => Additive (Tagged tag a) Source # | |
Defined in LLVM.Extra.Nice.Value.Private |
inc :: (Additive i, IntegerConstant i) => T i -> CodeGenFunction r (T i) Source #
dec :: (Additive i, IntegerConstant i) => T i -> CodeGenFunction r (T i) Source #
class Additive a => PseudoRing a where Source #
Instances
PseudoRing Int16 Source # | |
PseudoRing Int32 Source # | |
PseudoRing Int64 Source # | |
PseudoRing Int8 Source # | |
PseudoRing Word16 Source # | |
PseudoRing Word32 Source # | |
PseudoRing Word64 Source # | |
PseudoRing Word8 Source # | |
PseudoRing Double Source # | |
PseudoRing Float Source # | |
PseudoRing Int Source # | |
PseudoRing Word Source # | |
(Flags flags, NiceValue a, PseudoRing a) => PseudoRing (Number flags a) Source # | |
(Positive n, PseudoRing a) => PseudoRing (Vector n a) Source # | |
Defined in LLVM.Extra.Nice.Vector.Instance | |
PseudoRing a => PseudoRing (Tagged tag a) Source # | |
class PseudoRing a => Field a where Source #
type family Scalar vector Source #
Instances
type Scalar Double Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
type Scalar Float Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
type Scalar (Number flags a) Source # | |
Defined in LLVM.Extra.FastMath | |
type Scalar (Tagged tag a) Source # | |
Defined in LLVM.Extra.Nice.Value.Private |
class (PseudoRing (Scalar v), Additive v) => PseudoModule v where Source #
Instances
PseudoModule Double Source # | |
PseudoModule Float Source # | |
(Flags flags, NiceValue a, a ~ Scalar v, NiceValue v, PseudoModule v) => PseudoModule (Number flags v) Source # | |
PseudoModule a => PseudoModule (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 #
Instances
class (Repr i ~ Value ir, IsInteger ir, IntegerConstant ir, CmpRet ir, IsPrimitive ir) => NativeInteger i ir Source #
Instances
NativeInteger Int16 Int16 Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
NativeInteger Int32 Int32 Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
NativeInteger Int64 Int64 Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
NativeInteger Int8 Int8 Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
NativeInteger Word16 Word16 Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
NativeInteger Word32 Word32 Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
NativeInteger Word64 Word64 Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
NativeInteger Word8 Word8 Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
NativeInteger Int Int Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
NativeInteger Word Word Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
NativeInteger a a => NativeInteger (Tagged tag a) a Source # | |
Defined in LLVM.Extra.Nice.Value.Private |
class (Repr a ~ Value ar, IsFloating ar, RationalConstant ar, CmpRet ar, IsPrimitive ar) => NativeFloating a ar Source #
Instances
NativeFloating Double Double Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
NativeFloating Float Float Source # | |
Defined in LLVM.Extra.Nice.Value.Private |
truncateToInt :: (NativeInteger i ir, NativeFloating a ar) => T a -> CodeGenFunction r (T i) Source #
floorToInt :: (NativeInteger i ir, NativeFloating a ar) => T a -> CodeGenFunction r (T i) Source #
ceilingToInt :: (NativeInteger i ir, NativeFloating a ar) => T a -> CodeGenFunction r (T i) Source #
roundToIntFast :: (NativeInteger i ir, NativeFloating a ar) => T a -> CodeGenFunction r (T i) Source #
splitFractionToInt :: (NativeInteger i ir, NativeFloating a ar) => T a -> CodeGenFunction r (T (i, a)) Source #
class Field a => Algebraic a where Source #
Instances
Algebraic Double Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
Algebraic Float Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
(Flags flags, NiceValue a, Algebraic a) => Algebraic (Number flags a) Source # | |
Defined in LLVM.Extra.FastMath | |
Algebraic a => Algebraic (Tagged tag a) Source # | |
Defined in LLVM.Extra.Nice.Value.Private |
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 #
Instances
class C a => Select a where Source #
Instances
Select Int16 Source # | |
Select Int32 Source # | |
Select Int64 Source # | |
Select Int8 Source # | |
Select Word16 Source # | |
Select Word32 Source # | |
Select Word64 Source # | |
Select Word8 Source # | |
Select Bool8 Source # | |
Select Bool Source # | |
Select Double Source # | |
Select Float Source # | |
Select Int Source # | |
Select Word Source # | |
(Flags flags, NiceValue a, Select a) => Select (Number flags a) Source # | |
(Select a, Select b) => Select (a, b) Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
Select a => Select (Tagged tag a) Source # | |
(Select a, Select b, Select c) => Select (a, b, c) Source # | |
Defined in LLVM.Extra.Nice.Value.Private |
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
class Comparison a => FloatingComparison a where Source #
Methods
fcmp :: FPPredicate -> T a -> T a -> CodeGenFunction r (T Bool) Source #
Instances
FloatingComparison Float Source # | |
Defined in LLVM.Extra.Nice.Value.Private | |
(Flags flags, NiceValue a, FloatingComparison a) => FloatingComparison (Number flags a) Source # | |
Defined in LLVM.Extra.FastMath | |
FloatingComparison a => FloatingComparison (Tagged tag a) Source # | |
Defined in LLVM.Extra.Nice.Value.Private |
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 #
Instances
class BitShift a where Source #
Instances
BitShift Int16 Source # | |
BitShift Int32 Source # | |
BitShift Int64 Source # | |
BitShift Int8 Source # | |
BitShift Word16 Source # | |
BitShift Word32 Source # | |
BitShift Word64 Source # | |
BitShift Word8 Source # | |
BitShift Int Source # | |
BitShift Word Source # | |
(Positive n, BitShift a) => BitShift (Vector n a) Source # | |
Defined in LLVM.Extra.Nice.Vector.Instance |
class PseudoRing a => Integral a where Source #
fromIntegral :: (NativeInteger i ir, NativeFloating a ar) => T i -> CodeGenFunction r (T a) Source #
Constructors
Array [a] |
Instances
Integer n => Foldable (Array n) Source # | |
Defined in LLVM.Extra.Nice.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 # elem :: Eq a => a -> Array n a -> Bool # maximum :: Ord a => Array n a -> a # minimum :: Ord a => Array n a -> a # | |
Integer n => Traversable (Array n) Source # | |
Integer n => Applicative (Array n) Source # | |
Integer n => Functor (Array n) Source # | |
Show a => Show (Array n a) Source # | |
Eq a => Eq (Array n a) Source # | |
(Natural n, C a, Natural (n :*: SizeOf (Struct a))) => C (Array n a) Source # | |
(Natural n, C a) => C (Array n a) Source # | |
Defined in LLVM.Extra.Nice.Value.Array | |
type Repr (Array n a) Source # | |
Defined in LLVM.Extra.Nice.Value.Array |
extractArrayValue :: (Natural n, ArrayIndex n i, C a) => i -> T (Array n a) -> CodeGenFunction r (T a) Source #