linear-accelerate-0.7.0.0: Lifting linear vector spaces into Accelerate

Copyright2014 Edward Kmett Charles Durham
[2015..2020] Trevor L. McDonell
LicenseBSD-style (see the file LICENSE)
MaintainerTrevor L. McDonell <trevor.mcdonell@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Array.Accelerate.Linear.V4

Contents

Description

4-D Vectors

Synopsis

Documentation

data V4 a #

A 4-dimensional vector.

Constructors

V4 !a !a !a !a 
Instances
Monad V4 
Instance details

Defined in Linear.V4

Methods

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

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

return :: a -> V4 a #

fail :: String -> V4 a #

Functor V4 
Instance details

Defined in Linear.V4

Methods

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

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

MonadFix V4 
Instance details

Defined in Linear.V4

Methods

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

Applicative V4 
Instance details

Defined in Linear.V4

Methods

pure :: a -> V4 a #

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

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

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

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

Foldable V4 
Instance details

Defined in Linear.V4

Methods

fold :: Monoid m => V4 m -> m #

foldMap :: Monoid m => (a -> m) -> V4 a -> m #

foldr :: (a -> b -> b) -> b -> V4 a -> b #

foldr' :: (a -> b -> b) -> b -> V4 a -> b #

foldl :: (b -> a -> b) -> b -> V4 a -> b #

foldl' :: (b -> a -> b) -> b -> V4 a -> b #

foldr1 :: (a -> a -> a) -> V4 a -> a #

foldl1 :: (a -> a -> a) -> V4 a -> a #

toList :: V4 a -> [a] #

null :: V4 a -> Bool #

length :: V4 a -> Int #

elem :: Eq a => a -> V4 a -> Bool #

maximum :: Ord a => V4 a -> a #

minimum :: Ord a => V4 a -> a #

sum :: Num a => V4 a -> a #

product :: Num a => V4 a -> a #

Traversable V4 
Instance details

Defined in Linear.V4

Methods

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

sequenceA :: Applicative f => V4 (f a) -> f (V4 a) #

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

sequence :: Monad m => V4 (m a) -> m (V4 a) #

Functor V4 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

fmap :: (Elt a, Elt b, Elt (V4 a), Elt (V4 b)) => (Exp a -> Exp b) -> Exp (V4 a) -> Exp (V4 b) #

(<$) :: (Elt a, Elt b, Elt (V4 a), Elt (V4 b)) => Exp a -> Exp (V4 b) -> Exp (V4 a) #

Distributive V4 
Instance details

Defined in Linear.V4

Methods

distribute :: Functor f => f (V4 a) -> V4 (f a) #

collect :: Functor f => (a -> V4 b) -> f a -> V4 (f b) #

distributeM :: Monad m => m (V4 a) -> V4 (m a) #

collectM :: Monad m => (a -> V4 b) -> m a -> V4 (m b) #

Representable V4 
Instance details

Defined in Linear.V4

Associated Types

type Rep V4 :: Type #

Methods

tabulate :: (Rep V4 -> a) -> V4 a #

index :: V4 a -> Rep V4 -> a #

Eq1 V4 
Instance details

Defined in Linear.V4

Methods

liftEq :: (a -> b -> Bool) -> V4 a -> V4 b -> Bool #

Ord1 V4 
Instance details

Defined in Linear.V4

Methods

liftCompare :: (a -> b -> Ordering) -> V4 a -> V4 b -> Ordering #

Read1 V4 
Instance details

Defined in Linear.V4

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V4 a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V4 a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V4 a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V4 a] #

Show1 V4 
Instance details

Defined in Linear.V4

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V4 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V4 a] -> ShowS #

MonadZip V4 
Instance details

Defined in Linear.V4

Methods

mzip :: V4 a -> V4 b -> V4 (a, b) #

mzipWith :: (a -> b -> c) -> V4 a -> V4 b -> V4 c #

munzip :: V4 (a, b) -> (V4 a, V4 b) #

Serial1 V4 
Instance details

Defined in Linear.V4

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V4 a -> m () #

deserializeWith :: MonadGet m => m a -> m (V4 a) #

Hashable1 V4 
Instance details

Defined in Linear.V4

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> V4 a -> Int #

Apply V4 
Instance details

Defined in Linear.V4

Methods

(<.>) :: V4 (a -> b) -> V4 a -> V4 b #

(.>) :: V4 a -> V4 b -> V4 b #

(<.) :: V4 a -> V4 b -> V4 a #

liftF2 :: (a -> b -> c) -> V4 a -> V4 b -> V4 c #

Traversable1 V4 
Instance details

Defined in Linear.V4

Methods

traverse1 :: Apply f => (a -> f b) -> V4 a -> f (V4 b) #

sequence1 :: Apply f => V4 (f b) -> f (V4 b) #

Trace V4 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V4 (V4 a) -> a #

diagonal :: V4 (V4 a) -> V4 a #

R4 V4 
Instance details

Defined in Linear.V4

Methods

_w :: Lens' (V4 a) a #

_xyzw :: Lens' (V4 a) (V4 a) #

R3 V4 
Instance details

Defined in Linear.V4

Methods

_z :: Lens' (V4 a) a #

_xyz :: Lens' (V4 a) (V3 a) #

R2 V4 
Instance details

Defined in Linear.V4

Methods

_y :: Lens' (V4 a) a #

_xy :: Lens' (V4 a) (V2 a) #

R1 V4 
Instance details

Defined in Linear.V4

Methods

_x :: Lens' (V4 a) a #

Finite V4 
Instance details

Defined in Linear.V4

Associated Types

type Size V4 :: Nat #

Methods

toV :: V4 a -> V (Size V4) a #

fromV :: V (Size V4) a -> V4 a #

Metric V4 
Instance details

Defined in Linear.V4

Methods

dot :: Num a => V4 a -> V4 a -> a #

quadrance :: Num a => V4 a -> a #

qd :: Num a => V4 a -> V4 a -> a #

distance :: Floating a => V4 a -> V4 a -> a #

norm :: Floating a => V4 a -> a #

signorm :: Floating a => V4 a -> V4 a #

Additive V4 
Instance details

Defined in Linear.V4

Methods

zero :: Num a => V4 a #

(^+^) :: Num a => V4 a -> V4 a -> V4 a #

(^-^) :: Num a => V4 a -> V4 a -> V4 a #

lerp :: Num a => a -> V4 a -> V4 a -> V4 a #

liftU2 :: (a -> a -> a) -> V4 a -> V4 a -> V4 a #

liftI2 :: (a -> b -> c) -> V4 a -> V4 b -> V4 c #

Foldable1 V4 
Instance details

Defined in Linear.V4

Methods

fold1 :: Semigroup m => V4 m -> m #

foldMap1 :: Semigroup m => (a -> m) -> V4 a -> m #

toNonEmpty :: V4 a -> NonEmpty a #

Bind V4 
Instance details

Defined in Linear.V4

Methods

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

join :: V4 (V4 a) -> V4 a #

Additive V4 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

zero :: (Elt (V4 a), Num a) => Exp (V4 a) Source #

(^+^) :: (Num a, Box V4 a) => Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) Source #

(^-^) :: (Num a, Box V4 a) => Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) Source #

lerp :: (Num a, Box V4 a) => Exp a -> Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) Source #

Metric V4 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

dot :: (Num a, Box V4 a) => Exp (V4 a) -> Exp (V4 a) -> Exp a Source #

quadrance :: (Num a, Box V4 a) => Exp (V4 a) -> Exp a Source #

qd :: (Num a, Box V4 a) => Exp (V4 a) -> Exp (V4 a) -> Exp a Source #

distance :: (Floating a, Box V4 a) => Exp (V4 a) -> Exp (V4 a) -> Exp a Source #

norm :: (Floating a, Box V4 a) => Exp (V4 a) -> Exp a Source #

signorm :: (Floating a, Box V4 a) => Exp (V4 a) -> Exp (V4 a) Source #

R1 V4 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

_x :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp a) Source #

R2 V4 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

_y :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp a) Source #

_xy :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp (V2 a)) Source #

R3 V4 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

_z :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp a) Source #

_xyz :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp (V3 a)) Source #

R4 V4 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

_w :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp a) Source #

_xyzw :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp (V4 a)) Source #

Trace V4 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.Trace

Methods

trace :: (Num a, Box2 V4 V4 a) => Exp (V4 (V4 a)) -> Exp a Source #

diagonal :: Box2 V4 V4 a => Exp (V4 (V4 a)) -> Exp (V4 a) Source #

(Lift Exp a, Elt (Plain a)) => Lift Exp (V4 a) Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Associated Types

type Plain (V4 a) :: Type #

Methods

lift :: V4 a -> Exp (Plain (V4 a)) #

Elt a => Unlift Exp (V4 (Exp a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

unlift :: Exp (Plain (V4 (Exp a))) -> V4 (Exp a) #

Unbox a => Vector Vector (V4 a) 
Instance details

Defined in Linear.V4

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (V4 a) -> m (Vector (V4 a)) #

basicUnsafeThaw :: PrimMonad m => Vector (V4 a) -> m (Mutable Vector (PrimState m) (V4 a)) #

basicLength :: Vector (V4 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V4 a) -> Vector (V4 a) #

basicUnsafeIndexM :: Monad m => Vector (V4 a) -> Int -> m (V4 a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (V4 a) -> Vector (V4 a) -> m () #

elemseq :: Vector (V4 a) -> V4 a -> b -> b #

Unbox a => MVector MVector (V4 a) 
Instance details

Defined in Linear.V4

Methods

basicLength :: MVector s (V4 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V4 a) -> MVector s (V4 a) #

basicOverlaps :: MVector s (V4 a) -> MVector s (V4 a) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (V4 a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (V4 a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> V4 a -> m (MVector (PrimState m) (V4 a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (V4 a) -> Int -> m (V4 a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (V4 a) -> Int -> V4 a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (V4 a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (V4 a) -> V4 a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (V4 a) -> MVector (PrimState m) (V4 a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (V4 a) -> MVector (PrimState m) (V4 a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (V4 a) -> Int -> m (MVector (PrimState m) (V4 a)) #

Bounded a => Bounded (Exp (V4 a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

minBound :: Exp (V4 a) #

maxBound :: Exp (V4 a) #

Bounded a => Bounded (V4 a) 
Instance details

Defined in Linear.V4

Methods

minBound :: V4 a #

maxBound :: V4 a #

Eq a => Eq (V4 a) 
Instance details

Defined in Linear.V4

Methods

(==) :: V4 a -> V4 a -> Bool #

(/=) :: V4 a -> V4 a -> Bool #

Floating a => Floating (Exp (V4 a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

pi :: Exp (V4 a) #

exp :: Exp (V4 a) -> Exp (V4 a) #

log :: Exp (V4 a) -> Exp (V4 a) #

sqrt :: Exp (V4 a) -> Exp (V4 a) #

(**) :: Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) #

logBase :: Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) #

sin :: Exp (V4 a) -> Exp (V4 a) #

cos :: Exp (V4 a) -> Exp (V4 a) #

tan :: Exp (V4 a) -> Exp (V4 a) #

asin :: Exp (V4 a) -> Exp (V4 a) #

acos :: Exp (V4 a) -> Exp (V4 a) #

atan :: Exp (V4 a) -> Exp (V4 a) #

sinh :: Exp (V4 a) -> Exp (V4 a) #

cosh :: Exp (V4 a) -> Exp (V4 a) #

tanh :: Exp (V4 a) -> Exp (V4 a) #

asinh :: Exp (V4 a) -> Exp (V4 a) #

acosh :: Exp (V4 a) -> Exp (V4 a) #

atanh :: Exp (V4 a) -> Exp (V4 a) #

log1p :: Exp (V4 a) -> Exp (V4 a) #

expm1 :: Exp (V4 a) -> Exp (V4 a) #

log1pexp :: Exp (V4 a) -> Exp (V4 a) #

log1mexp :: Exp (V4 a) -> Exp (V4 a) #

Floating a => Floating (V4 a) 
Instance details

Defined in Linear.V4

Methods

pi :: V4 a #

exp :: V4 a -> V4 a #

log :: V4 a -> V4 a #

sqrt :: V4 a -> V4 a #

(**) :: V4 a -> V4 a -> V4 a #

logBase :: V4 a -> V4 a -> V4 a #

sin :: V4 a -> V4 a #

cos :: V4 a -> V4 a #

tan :: V4 a -> V4 a #

asin :: V4 a -> V4 a #

acos :: V4 a -> V4 a #

atan :: V4 a -> V4 a #

sinh :: V4 a -> V4 a #

cosh :: V4 a -> V4 a #

tanh :: V4 a -> V4 a #

asinh :: V4 a -> V4 a #

acosh :: V4 a -> V4 a #

atanh :: V4 a -> V4 a #

log1p :: V4 a -> V4 a #

expm1 :: V4 a -> V4 a #

log1pexp :: V4 a -> V4 a #

log1mexp :: V4 a -> V4 a #

Floating a => Fractional (Exp (V4 a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

(/) :: Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) #

recip :: Exp (V4 a) -> Exp (V4 a) #

fromRational :: Rational -> Exp (V4 a) #

Fractional a => Fractional (V4 a) 
Instance details

Defined in Linear.V4

Methods

(/) :: V4 a -> V4 a -> V4 a #

recip :: V4 a -> V4 a #

fromRational :: Rational -> V4 a #

Data a => Data (V4 a) 
Instance details

Defined in Linear.V4

Methods

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

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

toConstr :: V4 a -> Constr #

dataTypeOf :: V4 a -> DataType #

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

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

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

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

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

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

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

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

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

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

Num a => Num (Exp (V4 a)) Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

(+) :: Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) #

(-) :: Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) #

(*) :: Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) #

negate :: Exp (V4 a) -> Exp (V4 a) #

abs :: Exp (V4 a) -> Exp (V4 a) #

signum :: Exp (V4 a) -> Exp (V4 a) #

fromInteger :: Integer -> Exp (V4 a) #

Num a => Num (V4 a) 
Instance details

Defined in Linear.V4

Methods

(+) :: V4 a -> V4 a -> V4 a #

(-) :: V4 a -> V4 a -> V4 a #

(*) :: V4 a -> V4 a -> V4 a #

negate :: V4 a -> V4 a #

abs :: V4 a -> V4 a #

signum :: V4 a -> V4 a #

fromInteger :: Integer -> V4 a #

Ord a => Ord (V4 a) 
Instance details

Defined in Linear.V4

Methods

compare :: V4 a -> V4 a -> Ordering #

(<) :: V4 a -> V4 a -> Bool #

(<=) :: V4 a -> V4 a -> Bool #

(>) :: V4 a -> V4 a -> Bool #

(>=) :: V4 a -> V4 a -> Bool #

max :: V4 a -> V4 a -> V4 a #

min :: V4 a -> V4 a -> V4 a #

Read a => Read (V4 a) 
Instance details

Defined in Linear.V4

Show a => Show (V4 a) 
Instance details

Defined in Linear.V4

Methods

showsPrec :: Int -> V4 a -> ShowS #

show :: V4 a -> String #

showList :: [V4 a] -> ShowS #

Ix a => Ix (V4 a) 
Instance details

Defined in Linear.V4

Methods

range :: (V4 a, V4 a) -> [V4 a] #

index :: (V4 a, V4 a) -> V4 a -> Int #

unsafeIndex :: (V4 a, V4 a) -> V4 a -> Int

inRange :: (V4 a, V4 a) -> V4 a -> Bool #

rangeSize :: (V4 a, V4 a) -> Int #

unsafeRangeSize :: (V4 a, V4 a) -> Int

Generic (V4 a) 
Instance details

Defined in Linear.V4

Associated Types

type Rep (V4 a) :: Type -> Type #

Methods

from :: V4 a -> Rep (V4 a) x #

to :: Rep (V4 a) x -> V4 a #

Semigroup a => Semigroup (V4 a) 
Instance details

Defined in Linear.V4

Methods

(<>) :: V4 a -> V4 a -> V4 a #

sconcat :: NonEmpty (V4 a) -> V4 a #

stimes :: Integral b => b -> V4 a -> V4 a #

Monoid a => Monoid (V4 a) 
Instance details

Defined in Linear.V4

Methods

mempty :: V4 a #

mappend :: V4 a -> V4 a -> V4 a #

mconcat :: [V4 a] -> V4 a #

Lift a => Lift (V4 a) 
Instance details

Defined in Linear.V4

Methods

lift :: V4 a -> Q Exp #

Ord a => Ord (V4 a) Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

(<) :: Exp (V4 a) -> Exp (V4 a) -> Exp Bool #

(>) :: Exp (V4 a) -> Exp (V4 a) -> Exp Bool #

(<=) :: Exp (V4 a) -> Exp (V4 a) -> Exp Bool #

(>=) :: Exp (V4 a) -> Exp (V4 a) -> Exp Bool #

min :: Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) #

max :: Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) #

compare :: Exp (V4 a) -> Exp (V4 a) -> Exp Ordering #

Eq a => Eq (V4 a) Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

(==) :: Exp (V4 a) -> Exp (V4 a) -> Exp Bool #

(/=) :: Exp (V4 a) -> Exp (V4 a) -> Exp Bool #

Elt a => Elt (V4 a) Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Associated Types

type EltR (V4 a) :: Type

Methods

eltR :: TypeR (EltR (V4 a))

tagsR :: [TagR (EltR (V4 a))]

fromElt :: V4 a -> EltR (V4 a)

toElt :: EltR (V4 a) -> V4 a

Storable a => Storable (V4 a) 
Instance details

Defined in Linear.V4

Methods

sizeOf :: V4 a -> Int #

alignment :: V4 a -> Int #

peekElemOff :: Ptr (V4 a) -> Int -> IO (V4 a) #

pokeElemOff :: Ptr (V4 a) -> Int -> V4 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (V4 a) #

pokeByteOff :: Ptr b -> Int -> V4 a -> IO () #

peek :: Ptr (V4 a) -> IO (V4 a) #

poke :: Ptr (V4 a) -> V4 a -> IO () #

Binary a => Binary (V4 a) 
Instance details

Defined in Linear.V4

Methods

put :: V4 a -> Put #

get :: Get (V4 a) #

putList :: [V4 a] -> Put #

Serial a => Serial (V4 a) 
Instance details

Defined in Linear.V4

Methods

serialize :: MonadPut m => V4 a -> m () #

deserialize :: MonadGet m => m (V4 a) #

Serialize a => Serialize (V4 a) 
Instance details

Defined in Linear.V4

Methods

put :: Putter (V4 a) #

get :: Get (V4 a) #

NFData a => NFData (V4 a) 
Instance details

Defined in Linear.V4

Methods

rnf :: V4 a -> () #

Hashable a => Hashable (V4 a) 
Instance details

Defined in Linear.V4

Methods

hashWithSalt :: Int -> V4 a -> Int #

hash :: V4 a -> Int #

Unbox a => Unbox (V4 a) 
Instance details

Defined in Linear.V4

Ixed (V4 a) 
Instance details

Defined in Linear.V4

Methods

ix :: Index (V4 a) -> Traversal' (V4 a) (IxValue (V4 a)) #

Epsilon a => Epsilon (V4 a) 
Instance details

Defined in Linear.V4

Methods

nearZero :: V4 a -> Bool #

Random a => Random (V4 a) 
Instance details

Defined in Linear.V4

Methods

randomR :: RandomGen g => (V4 a, V4 a) -> g -> (V4 a, g) #

random :: RandomGen g => g -> (V4 a, g) #

randomRs :: RandomGen g => (V4 a, V4 a) -> g -> [V4 a] #

randoms :: RandomGen g => g -> [V4 a] #

randomRIO :: (V4 a, V4 a) -> IO (V4 a) #

randomIO :: IO (V4 a) #

Epsilon a => Epsilon (V4 a) Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

nearZero :: Exp (V4 a) -> Exp Bool Source #

Generic1 V4 
Instance details

Defined in Linear.V4

Associated Types

type Rep1 V4 :: k -> Type #

Methods

from1 :: V4 a -> Rep1 V4 a #

to1 :: Rep1 V4 a -> V4 a #

FunctorWithIndex (E V4) V4 
Instance details

Defined in Linear.V4

Methods

imap :: (E V4 -> a -> b) -> V4 a -> V4 b #

imapped :: IndexedSetter (E V4) (V4 a) (V4 b) a b #

FoldableWithIndex (E V4) V4 
Instance details

Defined in Linear.V4

Methods

ifoldMap :: Monoid m => (E V4 -> a -> m) -> V4 a -> m #

ifolded :: IndexedFold (E V4) (V4 a) a #

ifoldr :: (E V4 -> a -> b -> b) -> b -> V4 a -> b #

ifoldl :: (E V4 -> b -> a -> b) -> b -> V4 a -> b #

ifoldr' :: (E V4 -> a -> b -> b) -> b -> V4 a -> b #

ifoldl' :: (E V4 -> b -> a -> b) -> b -> V4 a -> b #

TraversableWithIndex (E V4) V4 
Instance details

Defined in Linear.V4

Methods

itraverse :: Applicative f => (E V4 -> a -> f b) -> V4 a -> f (V4 b) #

itraversed :: IndexedTraversal (E V4) (V4 a) (V4 b) a b #

Each (V4 a) (V4 b) a b 
Instance details

Defined in Linear.V4

Methods

each :: Traversal (V4 a) (V4 b) a b #

Field1 (V4 a) (V4 a) a a 
Instance details

Defined in Linear.V4

Methods

_1 :: Lens (V4 a) (V4 a) a a #

Field2 (V4 a) (V4 a) a a 
Instance details

Defined in Linear.V4

Methods

_2 :: Lens (V4 a) (V4 a) a a #

Field3 (V4 a) (V4 a) a a 
Instance details

Defined in Linear.V4

Methods

_3 :: Lens (V4 a) (V4 a) a a #

Field4 (V4 a) (V4 a) a a 
Instance details

Defined in Linear.V4

Methods

_4 :: Lens (V4 a) (V4 a) a a #

(Elt a, Elt b) => Each (Exp (V4 a)) (Exp (V4 b)) (Exp a) (Exp b) Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

each :: Traversal (Exp (V4 a)) (Exp (V4 b)) (Exp a) (Exp b) #

type Rep V4 
Instance details

Defined in Linear.V4

type Rep V4 = E V4
type Size V4 
Instance details

Defined in Linear.V4

type Size V4 = 4
data MVector s (V4 a) 
Instance details

Defined in Linear.V4

data MVector s (V4 a) = MV_V4 !Int !(MVector s a)
type Rep (V4 a) 
Instance details

Defined in Linear.V4

type EltR (V4 a) 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

type EltR (V4 a) = GEltR () (Rep (V4 a))
type Plain (V4 a) Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

type Plain (V4 a) = V4 (Plain a)
data Vector (V4 a) 
Instance details

Defined in Linear.V4

data Vector (V4 a) = V_V4 !Int !(Vector a)
type Index (V4 a) 
Instance details

Defined in Linear.V4

type Index (V4 a) = E V4
type IxValue (V4 a) 
Instance details

Defined in Linear.V4

type IxValue (V4 a) = a
type Rep1 V4 
Instance details

Defined in Linear.V4

pattern V4_ :: Elt a => Exp a -> Exp a -> Exp a -> Exp a -> Exp (V4 a) Source #

vector :: forall a. Num a => Exp (V3 a) -> Exp (V4 a) Source #

Convert a 3-dimensional affine vector into a 4-dimensional homogeneous vector.

point :: forall a. Num a => Exp (V3 a) -> Exp (V4 a) Source #

Convert a 3-dimensional affine point into a 4-dimensional homogeneous vector.

normalizePoint :: forall a. Fractional a => Exp (V4 a) -> Exp (V3 a) Source #

Convert 4-dimensional projective coordinates to a 3-dimensional point. This operation may be denoted, euclidean [x:y:z:w] = (x/w, y/w, z/w) where the projective, homogenous, coordinate [x:y:z:w] is one of many associated with a single point (x/w, y/w, z/w).

class R1 t => R1 t where Source #

A space that has at least 1 basis vector _x.

Minimal complete definition

Nothing

Methods

_x :: (Elt a, Box t a) => Lens' (Exp (t a)) (Exp a) Source #

>>> test $ (V1_ 2 :: Exp (V1 Int)) ^. _x
2
>>> test $ (V1_ 2 :: Exp (V1 Int)) & _x .~ 3
V1 3
Instances
R1 V4 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

_x :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp a) Source #

R1 V3 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V3

Methods

_x :: (Elt a, Box V3 a) => Lens' (Exp (V3 a)) (Exp a) Source #

R1 V2 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V2

Methods

_x :: (Elt a, Box V2 a) => Lens' (Exp (V2 a)) (Exp a) Source #

R1 V1 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V1

Methods

_x :: (Elt a, Box V1 a) => Lens' (Exp (V1 a)) (Exp a) Source #

class (R2 t, R1 t) => R2 t where Source #

A space that distinguishes 2 orthogonal basis vectors _x and _y, but may have more.

Minimal complete definition

Nothing

Methods

_y :: (Elt a, Box t a) => Lens' (Exp (t a)) (Exp a) Source #

>>> test $ (V2_ 1 2 :: Exp (V2 Int)) ^. _y
2
>>> test $ (V2_ 1 2 :: Exp (V2 Int)) & _y .~ 3
V2 1 3

_xy :: (Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V2 a)) Source #

Instances
R2 V4 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

_y :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp a) Source #

_xy :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp (V2 a)) Source #

R2 V3 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V3

Methods

_y :: (Elt a, Box V3 a) => Lens' (Exp (V3 a)) (Exp a) Source #

_xy :: (Elt a, Box V3 a) => Lens' (Exp (V3 a)) (Exp (V2 a)) Source #

R2 V2 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V2

Methods

_y :: (Elt a, Box V2 a) => Lens' (Exp (V2 a)) (Exp a) Source #

_xy :: (Elt a, Box V2 a) => Lens' (Exp (V2 a)) (Exp (V2 a)) Source #

_yx :: forall t a. (R2 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V2 a)) Source #

>>> test $ (V2_ 1 2 :: Exp (V2 Int)) ^. _yx
V2 2 1

class (R3 t, R2 t) => R3 t where Source #

A space that distinguishes 3 orthogonal basis vectors: _x, _y, and _z. (Although it may have more)

Minimal complete definition

Nothing

Methods

_z :: forall a. (Elt a, Box t a) => Lens' (Exp (t a)) (Exp a) Source #

>>> test $ (V3_ 1 2 3 :: Exp (V3 Int)) ^. _z
3
>>> test $ (V3_ 1 2 3 :: Exp (V3 Int)) & _z .~ 42
V3 1 2 42

_xyz :: forall a. (Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

Instances
R3 V4 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

_z :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp a) Source #

_xyz :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp (V3 a)) Source #

R3 V3 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V3

Methods

_z :: (Elt a, Box V3 a) => Lens' (Exp (V3 a)) (Exp a) Source #

_xyz :: (Elt a, Box V3 a) => Lens' (Exp (V3 a)) (Exp (V3 a)) Source #

_xz :: forall t a. (R3 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V2 a)) Source #

_yz :: forall t a. (R3 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V2 a)) Source #

_zx :: forall t a. (R3 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V2 a)) Source #

_zy :: forall t a. (R3 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V2 a)) Source #

_xzy :: forall t a. (R3 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_yxz :: forall t a. (R3 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_yzx :: forall t a. (R3 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_zxy :: forall t a. (R3 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_zyx :: forall t a. (R3 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

class (R4 t, R3 t) => R4 t where Source #

A space that distinguishes orthogonal basis vectors _x, _y, _z, and _w. (Although it may have more.)

Minimal complete definition

Nothing

Methods

_w :: forall a. (Elt a, Box t a) => Lens' (Exp (t a)) (Exp a) Source #

>>> test $ (V4_ 1 2 3 4 :: Exp (V4 Int)) ^. _w
4
>>> test $ (V4_ 1 2 3 4 :: Exp (V4 Int)) & _w .~ 42
V4 1 2 3 42

_xyzw :: forall a. (Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

Instances
R4 V4 Source # 
Instance details

Defined in Data.Array.Accelerate.Linear.V4

Methods

_w :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp a) Source #

_xyzw :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp (V4 a)) Source #

_xw :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V2 a)) Source #

_yw :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V2 a)) Source #

_zw :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V2 a)) Source #

_wx :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V2 a)) Source #

_wy :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V2 a)) Source #

_wz :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V2 a)) Source #

_xyw :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_xzw :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_xwy :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_xwz :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_yxw :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_yzw :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_ywx :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_ywz :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_zxw :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_zyw :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_zwx :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_zwy :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_wxy :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_wxz :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_wyx :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_wyz :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_wzx :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_wzy :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V3 a)) Source #

_xywz :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_xzyw :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_xzwy :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_xwyz :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_xwzy :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_yxzw :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_yxwz :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_yzxw :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_yzwx :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_ywxz :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_ywzx :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_zxyw :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_zxwy :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_zyxw :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_zywx :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_zwxy :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_zwyx :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_wxyz :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_wxzy :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_wyxz :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_wyzx :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_wzxy :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

_wzyx :: forall t a. (R4 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V4 a)) Source #

ex :: R1 t => E t Source #

ey :: R2 t => E t Source #

ez :: R3 t => E t Source #

ew :: R4 t => E t Source #

Orphan instances

Functor V4 Source # 
Instance details

Methods

fmap :: (Elt a, Elt b, Elt (V4 a), Elt (V4 b)) => (Exp a -> Exp b) -> Exp (V4 a) -> Exp (V4 b) #

(<$) :: (Elt a, Elt b, Elt (V4 a), Elt (V4 b)) => Exp a -> Exp (V4 b) -> Exp (V4 a) #

Additive V4 Source # 
Instance details

Methods

zero :: (Elt (V4 a), Num a) => Exp (V4 a) Source #

(^+^) :: (Num a, Box V4 a) => Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) Source #

(^-^) :: (Num a, Box V4 a) => Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) Source #

lerp :: (Num a, Box V4 a) => Exp a -> Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) Source #

Metric V4 Source # 
Instance details

Methods

dot :: (Num a, Box V4 a) => Exp (V4 a) -> Exp (V4 a) -> Exp a Source #

quadrance :: (Num a, Box V4 a) => Exp (V4 a) -> Exp a Source #

qd :: (Num a, Box V4 a) => Exp (V4 a) -> Exp (V4 a) -> Exp a Source #

distance :: (Floating a, Box V4 a) => Exp (V4 a) -> Exp (V4 a) -> Exp a Source #

norm :: (Floating a, Box V4 a) => Exp (V4 a) -> Exp a Source #

signorm :: (Floating a, Box V4 a) => Exp (V4 a) -> Exp (V4 a) Source #

R1 V4 Source # 
Instance details

Methods

_x :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp a) Source #

R2 V4 Source # 
Instance details

Methods

_y :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp a) Source #

_xy :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp (V2 a)) Source #

R3 V4 Source # 
Instance details

Methods

_z :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp a) Source #

_xyz :: (Elt a, Box V4 a) => Lens' (Exp (V4 a)) (Exp (V3 a)) Source #

(Lift Exp a, Elt (Plain a)) => Lift Exp (V4 a) Source # 
Instance details

Associated Types

type Plain (V4 a) :: Type #

Methods

lift :: V4 a -> Exp (Plain (V4 a)) #

Elt a => Unlift Exp (V4 (Exp a)) Source # 
Instance details

Methods

unlift :: Exp (Plain (V4 (Exp a))) -> V4 (Exp a) #

Bounded a => Bounded (Exp (V4 a)) Source # 
Instance details

Methods

minBound :: Exp (V4 a) #

maxBound :: Exp (V4 a) #

Floating a => Floating (Exp (V4 a)) Source # 
Instance details

Methods

pi :: Exp (V4 a) #

exp :: Exp (V4 a) -> Exp (V4 a) #

log :: Exp (V4 a) -> Exp (V4 a) #

sqrt :: Exp (V4 a) -> Exp (V4 a) #

(**) :: Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) #

logBase :: Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) #

sin :: Exp (V4 a) -> Exp (V4 a) #

cos :: Exp (V4 a) -> Exp (V4 a) #

tan :: Exp (V4 a) -> Exp (V4 a) #

asin :: Exp (V4 a) -> Exp (V4 a) #

acos :: Exp (V4 a) -> Exp (V4 a) #

atan :: Exp (V4 a) -> Exp (V4 a) #

sinh :: Exp (V4 a) -> Exp (V4 a) #

cosh :: Exp (V4 a) -> Exp (V4 a) #

tanh :: Exp (V4 a) -> Exp (V4 a) #

asinh :: Exp (V4 a) -> Exp (V4 a) #

acosh :: Exp (V4 a) -> Exp (V4 a) #

atanh :: Exp (V4 a) -> Exp (V4 a) #

log1p :: Exp (V4 a) -> Exp (V4 a) #

expm1 :: Exp (V4 a) -> Exp (V4 a) #

log1pexp :: Exp (V4 a) -> Exp (V4 a) #

log1mexp :: Exp (V4 a) -> Exp (V4 a) #

Floating a => Fractional (Exp (V4 a)) Source # 
Instance details

Methods

(/) :: Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) #

recip :: Exp (V4 a) -> Exp (V4 a) #

fromRational :: Rational -> Exp (V4 a) #

Num a => Num (Exp (V4 a)) Source # 
Instance details

Methods

(+) :: Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) #

(-) :: Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) #

(*) :: Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) #

negate :: Exp (V4 a) -> Exp (V4 a) #

abs :: Exp (V4 a) -> Exp (V4 a) #

signum :: Exp (V4 a) -> Exp (V4 a) #

fromInteger :: Integer -> Exp (V4 a) #

Ord a => Ord (V4 a) Source # 
Instance details

Methods

(<) :: Exp (V4 a) -> Exp (V4 a) -> Exp Bool #

(>) :: Exp (V4 a) -> Exp (V4 a) -> Exp Bool #

(<=) :: Exp (V4 a) -> Exp (V4 a) -> Exp Bool #

(>=) :: Exp (V4 a) -> Exp (V4 a) -> Exp Bool #

min :: Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) #

max :: Exp (V4 a) -> Exp (V4 a) -> Exp (V4 a) #

compare :: Exp (V4 a) -> Exp (V4 a) -> Exp Ordering #

Eq a => Eq (V4 a) Source # 
Instance details

Methods

(==) :: Exp (V4 a) -> Exp (V4 a) -> Exp Bool #

(/=) :: Exp (V4 a) -> Exp (V4 a) -> Exp Bool #

Elt a => Elt (V4 a) Source # 
Instance details

Associated Types

type EltR (V4 a) :: Type

Methods

eltR :: TypeR (EltR (V4 a))

tagsR :: [TagR (EltR (V4 a))]

fromElt :: V4 a -> EltR (V4 a)

toElt :: EltR (V4 a) -> V4 a

Epsilon a => Epsilon (V4 a) Source # 
Instance details

Methods

nearZero :: Exp (V4 a) -> Exp Bool Source #

(Elt a, Elt b) => Each (Exp (V4 a)) (Exp (V4 b)) (Exp a) (Exp b) Source # 
Instance details

Methods

each :: Traversal (Exp (V4 a)) (Exp (V4 b)) (Exp a) (Exp b) #