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

Copyright2014 Edward Kmett Charles Durham
2015 Trevor L. McDonell
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Array.Accelerate.Linear.V1

Contents

Description

1-D Vectors

Synopsis

Documentation

newtype V1 a :: * -> * #

A 1-dimensional vector

>>> pure 1 :: V1 Int
V1 1
>>> V1 2 + V1 3
V1 5
>>> V1 2 * V1 3
V1 6
>>> sum (V1 2)
2

Constructors

V1 a 

Instances

Monad V1 

Methods

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

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

return :: a -> V1 a #

fail :: String -> V1 a #

Functor V1 

Methods

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

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

MonadFix V1 

Methods

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

Applicative V1 

Methods

pure :: a -> V1 a #

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

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

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

Foldable V1 

Methods

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

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

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

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

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

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

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

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

toList :: V1 a -> [a] #

null :: V1 a -> Bool #

length :: V1 a -> Int #

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

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

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

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

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

Traversable V1 

Methods

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

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

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

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

Generic1 V1 

Associated Types

type Rep1 (V1 :: * -> *) :: * -> * #

Methods

from1 :: V1 a -> Rep1 V1 a #

to1 :: Rep1 V1 a -> V1 a #

Distributive V1 

Methods

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

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

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

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

Representable V1 

Associated Types

type Rep (V1 :: * -> *) :: * #

Methods

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

index :: V1 a -> Rep V1 -> a #

Eq1 V1 

Methods

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

Ord1 V1 

Methods

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

Read1 V1 

Methods

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

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

Show1 V1 

Methods

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

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

MonadZip V1 

Methods

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

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

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

Serial1 V1 

Methods

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

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

Traversable1 V1 

Methods

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

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

Trace V1 

Methods

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

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

R1 V1 

Methods

_x :: Functor f => (a -> f a) -> V1 a -> f (V1 a) #

Finite V1 

Associated Types

type Size (V1 :: * -> *) :: Nat #

Methods

toV :: V1 a -> V Nat (Size V1) a #

fromV :: V Nat (Size V1) a -> V1 a #

Metric V1 

Methods

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

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

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

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

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

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

Additive V1 

Methods

zero :: Num a => V1 a #

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

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

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

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

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

Apply V1 

Methods

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

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

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

Bind V1 

Methods

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

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

Foldable1 V1 

Methods

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

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

toNonEmpty :: V1 a -> NonEmpty a #

R1 V1 Source # 

Methods

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

Trace V1 Source # 

Methods

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

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

Unbox a => Vector Vector (V1 a) 

Methods

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

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

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

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

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

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

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

Unbox a => MVector MVector (V1 a) 

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

Bounded a => Bounded (V1 a) 

Methods

minBound :: V1 a #

maxBound :: V1 a #

Eq a => Eq (V1 a) 

Methods

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

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

Floating a => Floating (V1 a) 

Methods

pi :: V1 a #

exp :: V1 a -> V1 a #

log :: V1 a -> V1 a #

sqrt :: V1 a -> V1 a #

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

logBase :: V1 a -> V1 a -> V1 a #

sin :: V1 a -> V1 a #

cos :: V1 a -> V1 a #

tan :: V1 a -> V1 a #

asin :: V1 a -> V1 a #

acos :: V1 a -> V1 a #

atan :: V1 a -> V1 a #

sinh :: V1 a -> V1 a #

cosh :: V1 a -> V1 a #

tanh :: V1 a -> V1 a #

asinh :: V1 a -> V1 a #

acosh :: V1 a -> V1 a #

atanh :: V1 a -> V1 a #

log1p :: V1 a -> V1 a #

expm1 :: V1 a -> V1 a #

log1pexp :: V1 a -> V1 a #

log1mexp :: V1 a -> V1 a #

Fractional a => Fractional (V1 a) 

Methods

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

recip :: V1 a -> V1 a #

fromRational :: Rational -> V1 a #

Data a => Data (V1 a) 

Methods

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

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

toConstr :: V1 a -> Constr #

dataTypeOf :: V1 a -> DataType #

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

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

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

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

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

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

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

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

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

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

Num a => Num (V1 a) 

Methods

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

(-) :: V1 a -> V1 a -> V1 a #

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

negate :: V1 a -> V1 a #

abs :: V1 a -> V1 a #

signum :: V1 a -> V1 a #

fromInteger :: Integer -> V1 a #

Ord a => Ord (V1 a) 

Methods

compare :: V1 a -> V1 a -> Ordering #

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

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

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

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

max :: V1 a -> V1 a -> V1 a #

min :: V1 a -> V1 a -> V1 a #

Read a => Read (V1 a) 
Show a => Show (V1 a) 

Methods

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

show :: V1 a -> String #

showList :: [V1 a] -> ShowS #

Ix a => Ix (V1 a) 

Methods

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

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

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

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

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

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

Generic (V1 a) 

Associated Types

type Rep (V1 a) :: * -> * #

Methods

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

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

Storable a => Storable (V1 a) 

Methods

sizeOf :: V1 a -> Int #

alignment :: V1 a -> Int #

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

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

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

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

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

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

Binary a => Binary (V1 a) 

Methods

put :: V1 a -> Put #

get :: Get (V1 a) #

putList :: [V1 a] -> Put #

Serial a => Serial (V1 a) 

Methods

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

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

Serialize a => Serialize (V1 a) 

Methods

put :: Putter (V1 a) #

get :: Get (V1 a) #

NFData a => NFData (V1 a) 

Methods

rnf :: V1 a -> () #

Hashable a => Hashable (V1 a) 

Methods

hashWithSalt :: Int -> V1 a -> Int #

hash :: V1 a -> Int #

Unbox a => Unbox (V1 a) 
Ixed (V1 a) 

Methods

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

Epsilon a => Epsilon (V1 a) 

Methods

nearZero :: V1 a -> Bool #

FunctorWithIndex (E V1) V1 

Methods

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

imapped :: (Indexable (E V1) p, Settable f) => p a (f b) -> V1 a -> f (V1 b) #

FoldableWithIndex (E V1) V1 

Methods

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

ifolded :: (Indexable (E V1) p, Contravariant f, Applicative f) => p a (f a) -> V1 a -> f (V1 a) #

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

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

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

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

TraversableWithIndex (E V1) V1 

Methods

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

itraversed :: (Indexable (E V1) p, Applicative f) => p a (f b) -> V1 a -> f (V1 b) #

Each (V1 a) (V1 b) a b 

Methods

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

type Rep1 V1 
type Rep1 V1 = D1 (MetaData "V1" "Linear.V1" "linear-1.20.7-LM9jZhdWZ2yIxbtdhUjC67" True) (C1 (MetaCons "V1" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep V1 
type Rep V1 = E V1
type Size V1 
type Size V1 = 1
data MVector s (V1 a) 
data MVector s (V1 a) = MV_V1 (MVector s a)
type Rep (V1 a) 
type Rep (V1 a) = D1 (MetaData "V1" "Linear.V1" "linear-1.20.7-LM9jZhdWZ2yIxbtdhUjC67" True) (C1 (MetaCons "V1" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type EltRepr (V1 a) 
type EltRepr (V1 a) = ((), EltRepr a)
type ProdRepr (V1 a) 
type ProdRepr (V1 a) = ((), a)
type Plain (V1 a) # 
type Plain (V1 a) = V1 (Plain a)
data Vector (V1 a) 
data Vector (V1 a) = V_V1 (Vector a)
type Index (V1 a) 
type Index (V1 a) = E V1
type IxValue (V1 a) 
type IxValue (V1 a) = a

class R1 t => R1 t where Source #

A space that has at least 1 basis vector _x.

Methods

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

>>> test $ lift (V1 2 :: V1 Int) ^._x
2
>>> test $ lift (V1 2 :: V1 Int) & _x .~ 3
V1 3

Instances

R1 V1 Source # 

Methods

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

ex :: R1 t => E t Source #

Orphan instances

Additive V1 Source # 

Methods

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

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

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

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

Metric V1 Source # 

Methods

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

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

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

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

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

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

cst a => IsProduct cst (V1 a) Source # 

Associated Types

type ProdRepr (V1 a) :: *

Methods

fromProd :: proxy cst -> V1 a -> ProdRepr (V1 a)

toProd :: proxy cst -> ProdRepr (V1 a) -> V1 a

prod :: proxy cst -> V1 a -> ProdR cst (ProdRepr (V1 a))

(Lift Exp a, Elt (Plain a)) => Lift Exp (V1 a) Source # 

Associated Types

type Plain (V1 a) :: * #

Methods

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

Elt a => Unlift Exp (V1 (Exp a)) Source # 

Methods

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

Floating a => Floating (Exp (V1 a)) Source # 

Methods

pi :: Exp (V1 a) #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Floating a => Fractional (Exp (V1 a)) Source # 

Methods

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

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

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

Num a => Num (Exp (V1 a)) Source # 

Methods

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

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

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

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

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

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

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

Elt a => Elt (V1 a) Source # 

Methods

eltType :: V1 a -> TupleType (EltRepr (V1 a))

fromElt :: V1 a -> EltRepr (V1 a)

toElt :: EltRepr (V1 a) -> V1 a

(Elt a, Elt b) => Each (Exp (V1 a)) (Exp (V1 b)) (Exp a) (Exp b) Source # 

Methods

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