neural-0.3.0.0: Neural Networks in native Haskell

Copyright(c) Lars Brünjes, 2016
LicenseMIT
Maintainerbrunjlar@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • Cpp
  • MonoLocalBinds
  • ScopedTypeVariables
  • GADTs
  • GADTSyntax
  • DataKinds
  • KindSignatures
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll

Data.Utils.Vector

Description

This module defines fixed-length vectors and some basic typeclass instances and operations for them.

Synopsis

Documentation

data Vector :: Nat -> * -> * Source #

Vector n a is the type of vectors of length n with elements of type a.

Instances

Functor (Vector n) Source # 

Methods

fmap :: (a -> b) -> Vector n a -> Vector n b #

(<$) :: a -> Vector n b -> Vector n a #

KnownNat n => Applicative (Vector n) Source # 

Methods

pure :: a -> Vector n a #

(<*>) :: Vector n (a -> b) -> Vector n a -> Vector n b #

(*>) :: Vector n a -> Vector n b -> Vector n b #

(<*) :: Vector n a -> Vector n b -> Vector n a #

Foldable (Vector n) Source # 

Methods

fold :: Monoid m => Vector n m -> m #

foldMap :: Monoid m => (a -> m) -> Vector n a -> m #

foldr :: (a -> b -> b) -> b -> Vector n a -> b #

foldr' :: (a -> b -> b) -> b -> Vector n a -> b #

foldl :: (b -> a -> b) -> b -> Vector n a -> b #

foldl' :: (b -> a -> b) -> b -> Vector n a -> b #

foldr1 :: (a -> a -> a) -> Vector n a -> a #

foldl1 :: (a -> a -> a) -> Vector n a -> a #

toList :: Vector n a -> [a] #

null :: Vector n a -> Bool #

length :: Vector n a -> Int #

elem :: Eq a => a -> Vector n a -> Bool #

maximum :: Ord a => Vector n a -> a #

minimum :: Ord a => Vector n a -> a #

sum :: Num a => Vector n a -> a #

product :: Num a => Vector n a -> a #

Traversable (Vector n) Source # 

Methods

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

sequenceA :: Applicative f => Vector n (f a) -> f (Vector n a) #

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

sequence :: Monad m => Vector n (m a) -> m (Vector n a) #

Eq a => Eq (Vector n a) Source # 

Methods

(==) :: Vector n a -> Vector n a -> Bool #

(/=) :: Vector n a -> Vector n a -> Bool #

(KnownNat n, Read a) => Read (Vector n a) Source # 
Show a => Show (Vector n a) Source # 

Methods

showsPrec :: Int -> Vector n a -> ShowS #

show :: Vector n a -> String #

showList :: [Vector n a] -> ShowS #

NFData a => NFData (Vector n a) Source # 

Methods

rnf :: Vector n a -> () #

(<%>) :: Num a => Vector n a -> Vector n a -> a Source #

The scalar product of two vectors of the same length.

>>> :set -XDataKinds
>>> cons 1 (cons 2 nil) <%> cons 3 (cons 4 nil) :: Int
11

nil :: Vector 0 a Source #

The vector of length zero.

cons :: forall a n. a -> Vector n a -> Vector (n + 1) a Source #

Prepends the specified element to the specified vector.

>>> cons False (cons True nil)
[False,True]

generate :: forall n a. KnownNat n => (Int -> a) -> Vector n a Source #

Generates a vector by applying the given function to each index.

>>> :set -XDataKinds
>>> generate id :: Vector 3 Int
[0,1,2]

(!?) :: Vector n a -> Int -> Maybe a Source #

Gets the vector element at the specified index if the index is valid, otherwise Nothing.

>>> cons 'x' nil !? 0
Just 'x'
>>> cons 'x' nil !? 1
Nothing

(!) :: Vector n a -> Int -> a Source #

Gets the vector element at the specified index, throws an exception if the index is invalid.

>>> cons 'x' nil ! 0
'x'

vhead :: 1 <= n => Vector n a -> a Source #

Gets the first element of a vector of length greater than zero.

>>> vhead (cons 'x' (cons 'y' nil))
'x'

vtail :: forall a n. 1 <= n => Vector n a -> Vector (n - 1) a Source #

For a vector of length greater than zero, gets the vector with its first element removed.

>>> vtail (cons 'x' (cons 'y' nil))
"y"

(<+>) :: (Num a, KnownNat n) => Vector n a -> Vector n a -> Vector n a infixl 6 Source #

Adds two vectors of the same length.

>>> :set -XDataKinds
>>> (cons 1 (cons 2 nil)) <+> (cons 3 (cons 4 nil)) :: Vector 2 Int
[4,6]

(<->) :: (Num a, KnownNat n) => Vector n a -> Vector n a -> Vector n a infixl 6 Source #

Subtracts two vectors of the same length.

>>> :set -XDataKinds
>>> (cons 1 (cons 2 nil)) <-> (cons 3 (cons 4 nil)) :: Vector 2 Int
[-2,-2]

sqNorm :: Num a => Vector n a -> a Source #

Calculates the squared euclidean norm of a vector, i.e. the scalar product of the vector by itself.

>>> :set -XDataKinds
>>> sqNorm (cons 3 (cons 4 nil)) :: Int
25

sqDiff :: (Num a, KnownNat n) => Vector n a -> Vector n a -> a Source #

Calculates the squared euclidean distance between two vectors of the same length.

>>> :set -XDataKinds
>>> sqDiff (cons 1 (cons 2 nil)) (cons 3 (cons 4 nil)) :: Int
8

class KnownNat n #

This class gives the integer associated with a type-level natural. There are instances of the class for every concrete literal: 0, 1, 2, etc.

Since: 4.7.0.0

Minimal complete definition

natSing

natVal :: KnownNat n => proxy n -> Integer #

Since: 4.7.0.0