typelevel-tensor-0.1.0.4: Tensors whose ranks and dimensions type-inferred and type-checked.

Safe HaskellSafe-Infered

Data.Tensor.TypeLevel

Description

A tensor algebra library. Main ingredients are :

Vec and :~ are data constructors for rank-1 tensor. This is essentially a touple of objects of the same type.

Vector is a class for rank-1 tensor.

Axis is an object for accessing the tensor components.

Synopsis

Documentation

data n :~ a Source

data constructor for constructing n+1-dimensional tensor from n-dimensional tensor.

Constructors

(n a) :~ a 

Instances

Traversable n => Functor (:~ n) 
(Applicative n, Traversable n) => Applicative (:~ n) 
Traversable n => Foldable (:~ n) 
Traversable n => Traversable (:~ n) 
Vector v => Vector (:~ v) 
(C a, VectorRing v a, C (v a)) => VectorRing (:~ v) a 
(Eq a, Eq (n a)) => Eq (:~ n a) 
(Ord (n a), Ord a) => Ord (:~ n a)

the last component contributes the most to the ordering

(Read a, Read (n a)) => Read (:~ n a) 
(Show a, Show (n a)) => Show (:~ n a) 
(Vector v, C a) => C (:~ v a) 

data Vec a Source

data constructor for 0-dimensional tensor.

Constructors

Vec 

Instances

Functor Vec 
Applicative Vec 
Foldable Vec 
Traversable Vec 
Vector Vec 
C a => VectorRing Vec a 
Eq (Vec a) 
Ord (Vec a) 
Read (Vec a) 
Show (Vec a) 
C a => C (Vec a)

Vector whose components are additive is also additive.

newtype Vector v => Axis v Source

An coordinate Axis , labeled by an integer. Axis also carries v, the container type for its corresponding vector. Therefore, An axis of one type can access only vectors of a fixed dimension, but of arbitrary type.

Constructors

Axis 

Fields

axisIndex :: Int
 

Instances

Eq (Axis v) 
Ord (Axis v) 
Vector v => Read (Axis v) 
Vector v => Show (Axis v) 

(!) :: Vector v => v a -> Axis v -> aSource

a component operator.

class Traversable v => Vector v whereSource

An object that allows component-wise access.

Methods

componentFSource

Arguments

:: Failure StringException f 
=> Axis v

the axis of the component you want

-> v a

the target vector

-> f a

the component, obtained within a Failure monad

Get a component within f, a context which allows Failure.

component :: Axis v -> v a -> aSource

Get a component. This computation may result in a runtime error, though, as long as the Axis is generated from library functions such as compose, there will be no error.

dimension :: v a -> IntSource

The dimension of the vector.

compose :: (Axis v -> a) -> v aSource

Create a Vector from a function that maps axis to components.

Instances

Vector Vec 
Vector v => Vector (:~ v) 

class (Vector v, C a) => VectorRing v a whereSource

VectorRing is a Vector whose components belongs to C, thus providing unit vectors.

Methods

unitVectorF :: Failure StringException f => Axis v -> f (v a)Source

A vector where Axisth component is unity but others are zero.

unitVector :: Axis v -> v aSource

pure but unsafe version means of obtaining a unitVector

Instances

C a => VectorRing Vec a 
(C a, VectorRing v a, C (v a)) => VectorRing (:~ v) a 

contract :: (Vector v, C a) => (Axis v -> a) -> aSource

Tensor contraction. Create a Vector from a function that maps axis to component, then sums over the axis and returns a.

type Vec0 = VecSource

Type synonyms