tensors-0.1.0: Tensor in Haskell

Copyright(c) 2018 Daniel YU
LicenseBSD3
MaintainerDaniel YU <leptonyu@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.Tensor

Contents

Description

Tensor In Haskell

In ghci

λ> :set -XDataKinds
λ> :set -XOverloadedLists
λ> import Data.Tensor
λ> a = identity :: Tensor '[3,3] Int
λ> a
[[1,0,0],
[0,1,0],
[0,0,1]]
λ> b = [1..9] :: Tensor '[3,3] Int
λ> b
[[1,2,3],
[4,5,6],
[7,8,9]]
λ> a + b
[[2,2,3],
[4,6,6],
[7,8,10]]
λ> a - b
[[0,-2,-3],
[-4,-4,-6],
[-7,-8,-8]]
λ> a * b
[[1,0,0],
[0,5,0],
[0,0,9]]
λ> a `dot` b
[[1,2,3],
[4,5,6],
[7,8,9]]
λ> :t a `dyad` b
a `dyad` b :: Tensor '[3, 3, 3, 3] Int
λ> contraction a (i0,i1)
3
λ> :t contraction a (i0,i1)
contraction a (i0,i1) :: Tensor '[] Int
λ> select a (i0,i0)
[1,0,0]
λ> select a (i0,i1)
[0,1,0]
λ> select a (i0,i2)
[0,0,1]
λ> c = 1 :: Tensor '[3,3] Int
λ> c
[[1,1,1],
[1,1,1],
[1,1,1]]
λ> d = [1..4] :: Tensor '[2,2] Int
λ> d
[[1,2],
[3,4]]
λ> transpose d
[[1,3],
[2,4]]
Synopsis

Tensor Definition

data Tensor (s :: [Nat]) n Source #

Definition of Tensor. s means shape of tensor.

identity :: Tensor '[3,3] Int
Instances
SingI s => Functor (Tensor s) Source # 
Instance details

Defined in Data.Tensor.Tensor

Methods

fmap :: (a -> b) -> Tensor s a -> Tensor s b #

(<$) :: a -> Tensor s b -> Tensor s a #

SingI s => Applicative (Tensor s) Source # 
Instance details

Defined in Data.Tensor.Tensor

Methods

pure :: a -> Tensor s a #

(<*>) :: Tensor s (a -> b) -> Tensor s a -> Tensor s b #

liftA2 :: (a -> b -> c) -> Tensor s a -> Tensor s b -> Tensor s c #

(*>) :: Tensor s a -> Tensor s b -> Tensor s b #

(<*) :: Tensor s a -> Tensor s b -> Tensor s a #

SingI s => Foldable (Tensor s) Source # 
Instance details

Defined in Data.Tensor.Tensor

Methods

fold :: Monoid m => Tensor s m -> m #

foldMap :: Monoid m => (a -> m) -> Tensor s a -> m #

foldr :: (a -> b -> b) -> b -> Tensor s a -> b #

foldr' :: (a -> b -> b) -> b -> Tensor s a -> b #

foldl :: (b -> a -> b) -> b -> Tensor s a -> b #

foldl' :: (b -> a -> b) -> b -> Tensor s a -> b #

foldr1 :: (a -> a -> a) -> Tensor s a -> a #

foldl1 :: (a -> a -> a) -> Tensor s a -> a #

toList :: Tensor s a -> [a] #

null :: Tensor s a -> Bool #

length :: Tensor s a -> Int #

elem :: Eq a => a -> Tensor s a -> Bool #

maximum :: Ord a => Tensor s a -> a #

minimum :: Ord a => Tensor s a -> a #

sum :: Num a => Tensor s a -> a #

product :: Num a => Tensor s a -> a #

SingI s => IsList (Tensor s n) Source # 
Instance details

Defined in Data.Tensor.Tensor

Associated Types

type Item (Tensor s n) :: * #

Methods

fromList :: [Item (Tensor s n)] -> Tensor s n #

fromListN :: Int -> [Item (Tensor s n)] -> Tensor s n #

toList :: Tensor s n -> [Item (Tensor s n)] #

(SingI s, Floating n) => Floating (Tensor s n) Source # 
Instance details

Defined in Data.Tensor.Tensor

Methods

pi :: Tensor s n #

exp :: Tensor s n -> Tensor s n #

log :: Tensor s n -> Tensor s n #

sqrt :: Tensor s n -> Tensor s n #

(**) :: Tensor s n -> Tensor s n -> Tensor s n #

logBase :: Tensor s n -> Tensor s n -> Tensor s n #

sin :: Tensor s n -> Tensor s n #

cos :: Tensor s n -> Tensor s n #

tan :: Tensor s n -> Tensor s n #

asin :: Tensor s n -> Tensor s n #

acos :: Tensor s n -> Tensor s n #

atan :: Tensor s n -> Tensor s n #

sinh :: Tensor s n -> Tensor s n #

cosh :: Tensor s n -> Tensor s n #

tanh :: Tensor s n -> Tensor s n #

asinh :: Tensor s n -> Tensor s n #

acosh :: Tensor s n -> Tensor s n #

atanh :: Tensor s n -> Tensor s n #

log1p :: Tensor s n -> Tensor s n #

expm1 :: Tensor s n -> Tensor s n #

log1pexp :: Tensor s n -> Tensor s n #

log1mexp :: Tensor s n -> Tensor s n #

(SingI s, Fractional n) => Fractional (Tensor s n) Source # 
Instance details

Defined in Data.Tensor.Tensor

Methods

(/) :: Tensor s n -> Tensor s n -> Tensor s n #

recip :: Tensor s n -> Tensor s n #

fromRational :: Rational -> Tensor s n #

(SingI s, Num n) => Num (Tensor s n) Source # 
Instance details

Defined in Data.Tensor.Tensor

Methods

(+) :: Tensor s n -> Tensor s n -> Tensor s n #

(-) :: Tensor s n -> Tensor s n -> Tensor s n #

(*) :: Tensor s n -> Tensor s n -> Tensor s n #

negate :: Tensor s n -> Tensor s n #

abs :: Tensor s n -> Tensor s n #

signum :: Tensor s n -> Tensor s n #

fromInteger :: Integer -> Tensor s n #

(SingI s, Show n) => Show (Tensor s n) Source # 
Instance details

Defined in Data.Tensor.Tensor

Methods

showsPrec :: Int -> Tensor s n -> ShowS #

show :: Tensor s n -> String #

showList :: [Tensor s n] -> ShowS #

type Item (Tensor s n) Source # 
Instance details

Defined in Data.Tensor.Tensor

type Item (Tensor s n) = n

identity :: forall s n. (SingI s, Num n) => Tensor s n Source #

Unit tensor of shape s, if all the indices are equal then return 1, otherwise return 0.

type Scalar n = Tensor '[] n Source #

Scalar is rank 0 of tensor

type Vector s n = Tensor '[s] n Source #

Vector is rank 1 of tensor

type Matrix a b n = Tensor '[a, b] n Source #

Matrix is rank 2 of tensor

type SimpleTensor (r :: Nat) (dim :: Nat) n = If ((==) dim 0) (Scalar n) (Tensor (Replicate r dim) n) Source #

Simple Tensor is rank r tensor, has `n^r` dimension in total.

SimpleTensor 2 3 Int == Matrix 3 3 Int == Tensor '[3,3] Int
SimpleTensor r 0 Int == Scalar Int

Tensor Index

data TensorIndex (shape :: [Nat]) Source #

Tensor Index, used to locate each point of tensor

Instances
SingI s => IsList (TensorIndex s) Source # 
Instance details

Defined in Data.Tensor.Index

Associated Types

type Item (TensorIndex s) :: * #

SingI s => Bounded (TensorIndex s) Source # 
Instance details

Defined in Data.Tensor.Index

SingI s => Enum (TensorIndex s) Source # 
Instance details

Defined in Data.Tensor.Index

Eq (TensorIndex shape) Source # 
Instance details

Defined in Data.Tensor.Index

Methods

(==) :: TensorIndex shape -> TensorIndex shape -> Bool #

(/=) :: TensorIndex shape -> TensorIndex shape -> Bool #

Ord (TensorIndex shape) Source # 
Instance details

Defined in Data.Tensor.Index

Methods

compare :: TensorIndex shape -> TensorIndex shape -> Ordering #

(<) :: TensorIndex shape -> TensorIndex shape -> Bool #

(<=) :: TensorIndex shape -> TensorIndex shape -> Bool #

(>) :: TensorIndex shape -> TensorIndex shape -> Bool #

(>=) :: TensorIndex shape -> TensorIndex shape -> Bool #

max :: TensorIndex shape -> TensorIndex shape -> TensorIndex shape #

min :: TensorIndex shape -> TensorIndex shape -> TensorIndex shape #

Show (TensorIndex shape) Source # 
Instance details

Defined in Data.Tensor.Index

Methods

showsPrec :: Int -> TensorIndex shape -> ShowS #

show :: TensorIndex shape -> String #

showList :: [TensorIndex shape] -> ShowS #

type Item (TensorIndex s) Source # 
Instance details

Defined in Data.Tensor.Index

type Item (TensorIndex s) = Int

type Index = [Int] Source #

Tensor Dimension

type TensorRank (s :: [Nat]) = Length s Source #

shape :: forall s n. SingI s => Tensor s n -> [Int] Source #

Shape of Tensor, is a list of integers, uniquely determine the shape of tensor.

rank :: SingI s => Tensor s n -> Int Source #

Rank of Tensor

Tensor Operation

Reshape Tensor

reshape :: (Product s ~ Product s', SingI s) => Tensor s n -> Tensor s' n Source #

Reshape a tensor to another tensor, with total dimensions are equal.

Clone Tensor

clone :: SingI s => Tensor s n -> Tensor s n Source #

Clone tensor to a new Vector based tensor

Transpose Tensor

type Transpose (a :: [Nat]) = Reverse a Source #

transpose :: SingI a => Tensor a n -> Tensor (Transpose a) n Source #

Transpose tensor completely

λ> a = [1..9] :: Tensor '[3,3] Int
λ> a
[[1,2,3],
[4,5,6],
[7,8,9]]
λ> transpose a
[[1,4,7],
[2,5,8],
[3,6,9]]

Dyadic Tensor

dyad' :: (r ~ (++) s t, SingI s, SingI t, SingI r) => (n -> m -> o) -> Tensor s n -> Tensor t m -> Tensor r o Source #

dyad :: (r ~ (++) s t, SingI s, SingI t, SingI r, Num n) => Tensor s n -> Tensor t n -> Tensor r n Source #

Dyadic Tensor

λ> a = [1..4] :: Tensor '[2,2] Int
λ> a
[[1,2],
[3,4]]
λ> :t a `dyad` a
a `dyad` a :: Tensor '[2, 2, 2, 2] Int
λ> a `dyad` a
[[[[1,2],
[3,4]],
[[2,4],
[6,8]]],
[[[3,6],
[9,12]],
[[4,8],
[12,16]]]]

Tensor Product

type DotTensor s1 s2 = (++) (Init s1) (Tail s2) Source #

dot :: (Last s ~ Head s', SingI (DotTensor s s'), SingI s, SingI s', Num n) => Tensor s n -> Tensor s' n -> Tensor (DotTensor s s') n Source #

Tensor Product

λ> a = [1..4] :: Tensor '[2,2] Int
λ> a
[[1,2],
[3,4]]
λ> a `dot` a
[[7,10],
[15,22]]
dot a b == contraction (dyad a b) (rank a - 1, rank a)

For rank 2 tensor, it is just matrix product.

Contraction Tensor

type ContractionCheck s x y = And '[(<) x y, (>=) x 0, (<) y (TensorRank s)] Source #

type Contraction s x y = DropIndex (DropIndex s y) x Source #

type family TensorDim (s :: [Nat]) (i :: Nat) :: Nat where ... Source #

Equations

TensorDim s i = (!!) s i 

type DropIndex (s :: [Nat]) (i :: Nat) = (++) (Fst (SplitAt i s)) (Tail (Snd (SplitAt i s))) Source #

contraction :: forall x y s s' n. (ContractionCheck s x y ~ True, s' ~ Contraction s x y, TensorDim s x ~ TensorDim s y, KnownNat x, KnownNat y, SingI s, SingI s', KnownNat (TensorDim s x), Num n) => Tensor s n -> (Proxy x, Proxy y) -> Tensor s' n Source #

Contraction Tensor

λ> a = [1..16] :: Tensor '[4,4] Int
λ> a
[[1,2,3,4],
[5,6,7,8],
[9,10,11,12],
[13,14,15,16]]
λ> contraction a (i0,i1)
34

In rank 2 tensor, contraction of tensor is just the trace.

Tensor Selection

(!) :: SingI s => Tensor s n -> TensorIndex s -> n Source #

Get value from tensor by index

type CheckDim dim s = And '[(>=) dim 0, (<) dim (Length s)] Source #

type CheckSelect dim i s = And '[CheckDim dim s, (>=) i 0, (<) i ((!!) s dim)] Source #

type Select i s = (++) (Take i s) (Tail (Drop i s)) Source #

select :: (CheckSelect dim i s ~ True, s' ~ Select dim s, SingI s, KnownNat dim, KnownNat i) => Tensor s n -> (Proxy dim, Proxy i) -> Tensor s' n Source #

Select i indexing of tensor

λ> a = identity :: Tensor '[4,4] Int
λ> select a (i0,i0)
[1,0,0,0]
λ> select a (i0,i1)
[0,1,0,0]

type CheckSlice dim from to s = And '[CheckDim dim s, CheckSelect dim from s, (<) from to, (<=) to ((!!) s dim)] Source #

type Slice dim from to s = Concat '[Take dim s, '[(-) to from], Tail (Drop dim s)] Source #

slice :: (CheckSlice dim from to s ~ True, s' ~ Slice dim from to s, KnownNat dim, KnownNat from, KnownNat ((-) to from), SingI s) => Tensor s n -> (Proxy dim, (Proxy from, Proxy to)) -> Tensor s' n Source #

Slice tensor

λ> a = identity :: Tensor '[4,4] Int
λ> a
[[1,0,0,0],
[0,1,0,0],
[0,0,1,0],
[0,0,0,1]]
λ> slice a (i0,(i1,i3))
[[0,1,0,0],
[0,0,1,0]]
λ> slice a (i1,(i1,i3))
[[0,0],
[1,0],
[0,1],
[0,0]]

expand :: (TensorRank s ~ TensorRank s', SingI s) => Tensor s n -> Tensor s' n Source #

Expand tensor

λ> a = identity :: Tensor '[2,2] Int
λ> a
[[1,0],
[0,1]]
λ> expand a :: Tensor '[4,4] Int
[[1,0,1,0],
[0,1,0,1],
[1,0,1,0],
[0,1,0,1]]

Matrix Operation

det :: forall a n. (KnownNat a, Num n, Eq n) => SimpleMatrix a n -> n Source #

Determinant of n x n matrix

λ> a = [2,0,1,3,0,0,2,2,1,2,1,34,3,2,34,4] :: Tensor '[4,4] Int
λ> a
[[2,0,1,3],
[0,0,2,2],
[1,2,1,34],
[3,2,34,4]]
λ> det a
520

This implementation is not so fast, it can calculate 8 x 8 in 1 second with all the num none zero on my computer. It should be faster if more zero in the matrix.

lu :: forall a n. (KnownNat a, Integral n) => SimpleMatrix a n -> (SimpleMatrix a n, SimpleMatrix a n, n) Source #

LU decomposition of n x n matrix

λ> a = [1,2,3,2,5,7,3,5,3]:: Tensor '[3,3] Int
λ> (l,u,m) = lu a
λ> l
[[1,0,0],
[2,1,0],
[3,-1,1]]
λ> u
[[1,2,3],
[0,1,1],
[0,0,-5]]
λ> m
1

det' :: forall a n. (KnownNat a, Integral n) => SimpleMatrix a n -> n Source #

Helper

runTensor :: SingI s => Tensor s n -> [Int] -> n Source #

Convert tensor to untyped function, for internal usage.