synapse-0.1.0.0: Synapse is a machine learning library written in pure Haskell.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Synapse.Tensors.Vec

Description

Implementation of mathematical vector.

Vec is only a newtype wrapper around Vector, which implements several mathematical operations on itself.

Vec offers meaningful abstraction and easy interface (you can unwrap it to perform more complex tasks).

Synopsis

Vec datatype and simple getters.

newtype Vec a Source #

Mathematical vector (collection of elements).

Constructors

Vec 

Fields

  • unVec :: Vector a

    Internal representation.

Instances

Instances details
Foldable Vec Source # 
Instance details

Defined in Synapse.Tensors.Vec

Methods

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

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

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

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

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

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

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

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

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

toList :: Vec a -> [a] #

null :: Vec a -> Bool #

length :: Vec a -> Int #

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

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

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

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

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

Traversable Vec Source # 
Instance details

Defined in Synapse.Tensors.Vec

Methods

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

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

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

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

Applicative Vec Source # 
Instance details

Defined in Synapse.Tensors.Vec

Methods

pure :: a -> Vec a #

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

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

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

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

Functor Vec Source # 
Instance details

Defined in Synapse.Tensors.Vec

Methods

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

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

Floating a => Floating (Vec a) Source # 
Instance details

Defined in Synapse.Tensors.Vec

Methods

pi :: Vec a #

exp :: Vec a -> Vec a #

log :: Vec a -> Vec a #

sqrt :: Vec a -> Vec a #

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

logBase :: Vec a -> Vec a -> Vec a #

sin :: Vec a -> Vec a #

cos :: Vec a -> Vec a #

tan :: Vec a -> Vec a #

asin :: Vec a -> Vec a #

acos :: Vec a -> Vec a #

atan :: Vec a -> Vec a #

sinh :: Vec a -> Vec a #

cosh :: Vec a -> Vec a #

tanh :: Vec a -> Vec a #

asinh :: Vec a -> Vec a #

acosh :: Vec a -> Vec a #

atanh :: Vec a -> Vec a #

log1p :: Vec a -> Vec a #

expm1 :: Vec a -> Vec a #

log1pexp :: Vec a -> Vec a #

log1mexp :: Vec a -> Vec a #

Num a => Num (Vec a) Source # 
Instance details

Defined in Synapse.Tensors.Vec

Methods

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

(-) :: Vec a -> Vec a -> Vec a #

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

negate :: Vec a -> Vec a #

abs :: Vec a -> Vec a #

signum :: Vec a -> Vec a #

fromInteger :: Integer -> Vec a #

Read a => Read (Vec a) Source # 
Instance details

Defined in Synapse.Tensors.Vec

Fractional a => Fractional (Vec a) Source # 
Instance details

Defined in Synapse.Tensors.Vec

Methods

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

recip :: Vec a -> Vec a #

fromRational :: Rational -> Vec a #

Show a => Show (Vec a) Source # 
Instance details

Defined in Synapse.Tensors.Vec

Methods

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

show :: Vec a -> String #

showList :: [Vec a] -> ShowS #

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

Defined in Synapse.Tensors.Vec

Methods

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

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

Symbolic a => Symbolic (Vec a) Source # 
Instance details

Defined in Synapse.Autograd

Methods

symbolicZero :: Vec a -> Vec a Source #

symbolicOne :: Vec a -> Vec a Source #

symbolicN :: Int -> Vec a -> Vec a Source #

Symbolic a => ElementwiseScalarOps (Symbol (Vec a)) Source # 
Instance details

Defined in Synapse.Autograd

Methods

(+.) :: Symbol (Vec a) -> DType (Symbol (Vec a)) -> Symbol (Vec a) Source #

(-.) :: Symbol (Vec a) -> DType (Symbol (Vec a)) -> Symbol (Vec a) Source #

(*.) :: Symbol (Vec a) -> DType (Symbol (Vec a)) -> Symbol (Vec a) Source #

(/.) :: Symbol (Vec a) -> DType (Symbol (Vec a)) -> Symbol (Vec a) Source #

(**.) :: Symbol (Vec a) -> DType (Symbol (Vec a)) -> Symbol (Vec a) Source #

elementsMin :: Symbol (Vec a) -> DType (Symbol (Vec a)) -> Symbol (Vec a) Source #

elementsMax :: Symbol (Vec a) -> DType (Symbol (Vec a)) -> Symbol (Vec a) Source #

ElementwiseScalarOps (Vec a) Source # 
Instance details

Defined in Synapse.Tensors.Vec

Methods

(+.) :: Vec a -> DType (Vec a) -> Vec a Source #

(-.) :: Vec a -> DType (Vec a) -> Vec a Source #

(*.) :: Vec a -> DType (Vec a) -> Vec a Source #

(/.) :: Vec a -> DType (Vec a) -> Vec a Source #

(**.) :: Vec a -> DType (Vec a) -> Vec a Source #

elementsMin :: Vec a -> DType (Vec a) -> Vec a Source #

elementsMax :: Vec a -> DType (Vec a) -> Vec a Source #

Indexable (Vec a) Source # 
Instance details

Defined in Synapse.Tensors.Vec

Associated Types

type Index (Vec a) Source #

Methods

unsafeIndex :: Vec a -> Index (Vec a) -> DType (Vec a) Source #

(!) :: Vec a -> Index (Vec a) -> DType (Vec a) Source #

(!?) :: Vec a -> Index (Vec a) -> Maybe (DType (Vec a)) Source #

Symbolic a => SingletonOps (SymbolVec a) Source # 
Instance details

Defined in Synapse.Autograd

SingletonOps (Vec a) Source # 
Instance details

Defined in Synapse.Tensors.Vec

Symbolic a => VecOps (SymbolVec a) Source # 
Instance details

Defined in Synapse.Autograd

Methods

dot :: SymbolVec a -> SymbolVec a -> SymbolVec a Source #

Num a => VecOps (Vec a) Source # 
Instance details

Defined in Synapse.Tensors.Vec

Methods

dot :: Vec a -> Vec a -> Vec a Source #

type DType (SymbolVec a) Source # 
Instance details

Defined in Synapse.Autograd

type DType (SymbolVec a) = a
type DType (Vec a) Source # 
Instance details

Defined in Synapse.Tensors.Vec

type DType (Vec a) = a
type Index (Vec a) Source # 
Instance details

Defined in Synapse.Tensors.Vec

type Index (Vec a) = Int

size :: Vec a -> Int Source #

Size of a vector - number of elements.

Constructors

empty :: Vec a Source #

Creates empty Vec.

singleton :: SingletonOps f => DType f -> f Source #

Initializes singleton container.

fromList :: [a] -> Vec a Source #

Creates Vec from list.

generate :: Int -> (Int -> a) -> Vec a Source #

Creates Vec of given length using generating function.

replicate :: Int -> a -> Vec a Source #

Creates Vec of given length filled with given element.

Concatenation and splitting

cons :: a -> Vec a -> Vec a Source #

Prepend Vec with given element.

snoc :: Vec a -> a -> Vec a Source #

Append Vec with given element.

(++) :: Vec a -> Vec a -> Vec a infixr 5 Source #

Concatenate two Vecs.

concat :: [Vec a] -> Vec a Source #

Concatenate all Vecs.

splitAt :: Int -> Vec a -> (Vec a, Vec a) Source #

Splits Vec into two Vecs at a given index.

Combining

map :: (a -> b) -> Vec a -> Vec b Source #

Map a function over a Vec.

imap :: (Int -> a -> b) -> Vec a -> Vec b Source #

Apply a function to every element of a Vec and its index.

for :: Vec a -> (a -> b) -> Vec b Source #

map with its arguments flipped.

zipWith :: (a -> b -> c) -> Vec a -> Vec b -> Vec c Source #

Zips two Vecs with the given function.

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

Zips two Vecs.

Mathematics

zeroes :: Num a => Int -> Vec a Source #

Creates Vec of given length filled with zeroes.

ones :: Num a => Int -> Vec a Source #

Creates Vec of given length filled with ones.

squaredMagnitude :: Num a => Vec a -> a Source #

Squared magnitude of a Vec.

magnitude :: Floating a => Vec a -> a Source #

Magnitude of a Vec.

clampMagnitude :: (Floating a, Ord a) => a -> Vec a -> Vec a Source #

Clamps Vec magnitude.

normalized :: Floating a => Vec a -> Vec a Source #

Normalizes Vec by dividing each component by Vec magnitude.

linearCombination :: Num a => [(a, Vec a)] -> Vec a Source #

Computes linear combination of Vecs. Returns empty Vec if empty list was passed to this function.

dot :: (VecOps f, Num (DType f)) => f -> f -> f Source #

Calculates dot product of two vectors.

angleBetween :: Floating a => Vec a -> Vec a -> a Source #

Calculates an angle between two Vecs.

lerp :: (Floating a, Ord a) => a -> Vec a -> Vec a -> Vec a Source #

Linearly interpolates between two Vecs. Given parameter will be clamped between [0.0, 1.0].