numhask-0.0.3: A numeric prelude

Safe HaskellNone
LanguageHaskell2010

NumHask.Naperian

Contents

Description

multi-dimensional representable numbers

Synopsis

Documentation

class (HasShape f, Representable f) => Naperian f Source #

Instances

class HasShape f where Source #

ToDo: integrate ni Naperian instance

Minimal complete definition

shape, ndim

Associated Types

type Shape f Source #

Methods

shape :: f a -> Shape f Source #

ndim :: f a -> Int Source #

Instances

HasShape SomeTensor Source # 

Associated Types

type Shape (SomeTensor :: * -> *) :: * Source #

HasShape SomeVector Source # 

Associated Types

type Shape (SomeVector :: * -> *) :: * Source #

HasShape SomeMatrix Source # 

Associated Types

type Shape (SomeMatrix :: * -> *) :: * Source #

KnownNat n => HasShape (Vector n) Source # 

Associated Types

type Shape (Vector n :: * -> *) :: * Source #

Methods

shape :: Vector n a -> Shape (Vector n) Source #

ndim :: Vector n a -> Int Source #

SingI [Nat] r => HasShape (Tensor [Nat] r) Source # 

Associated Types

type Shape (Tensor [Nat] r :: * -> *) :: * Source #

Methods

shape :: Tensor [Nat] r a -> Shape (Tensor [Nat] r) Source #

ndim :: Tensor [Nat] r a -> Int Source #

(KnownNat m, KnownNat n) => HasShape (Matrix Nat Nat m n) Source # 

Associated Types

type Shape (Matrix Nat Nat m n :: * -> *) :: * Source #

Methods

shape :: Matrix Nat Nat m n a -> Shape (Matrix Nat Nat m n) Source #

ndim :: Matrix Nat Nat m n a -> Int Source #

Orphan instances

(Naperian f, AdditiveMagma a) => AdditiveHomomorphic a (f a) Source # 

Methods

plushom :: a -> f a Source #

(Naperian f, MultiplicativeMagma a) => MultiplicativeHomomorphic a (f a) Source # 

Methods

timeshom :: a -> f a Source #

(Naperian f, AdditiveGroup a) => AdditiveGroup (f a) Source # 

Methods

(-) :: f a -> f a -> f a Source #

(Naperian f, Additive a) => Additive (f a) Source # 

Methods

(+) :: f a -> f a -> f a Source #

(Naperian f, AdditiveMonoidal a) => AdditiveMonoidal (f a) Source # 
(Naperian f, AdditiveInvertible a) => AdditiveInvertible (f a) Source # 

Methods

negate :: f a -> f a Source #

(Naperian f, AdditiveCommutative a) => AdditiveCommutative (f a) Source # 
(Naperian f, AdditiveAssociative a) => AdditiveAssociative (f a) Source # 
(Naperian f, AdditiveUnital a) => AdditiveUnital (f a) Source # 

Methods

zero :: f a Source #

(Naperian f, AdditiveMagma a) => AdditiveMagma (f a) Source # 

Methods

plus :: f a -> f a -> f a Source #

(Naperian f, MultiplicativeGroup a) => MultiplicativeGroup (f a) Source # 

Methods

(/) :: f a -> f a -> f a Source #

(Naperian f, Multiplicative a) => Multiplicative (f a) Source # 

Methods

(*) :: f a -> f a -> f a Source #

(Naperian f, MultiplicativeMonoidal a) => MultiplicativeMonoidal (f a) Source # 
(Naperian f, MultiplicativeInvertible a) => MultiplicativeInvertible (f a) Source # 

Methods

recip :: f a -> f a Source #

(Naperian f, MultiplicativeCommutative a) => MultiplicativeCommutative (f a) Source # 
(Naperian f, MultiplicativeAssociative a) => MultiplicativeAssociative (f a) Source # 
(Naperian f, MultiplicativeUnital a) => MultiplicativeUnital (f a) Source # 

Methods

one :: f a Source #

(Naperian f, MultiplicativeMagma a) => MultiplicativeMagma (f a) Source # 

Methods

times :: f a -> f a -> f a Source #

(Naperian f, MultiplicativeMagma a, Additive a) => Distribution (f a) Source # 
(Naperian f, CRing a) => CRing (f a) Source # 
(Naperian f, Ring a) => Ring (f a) Source # 
(Naperian f, Semiring a) => Semiring (f a) Source # 
(Naperian f, BoundedField a, Foldable f) => BoundedField (f a) Source # 

Methods

maxBound :: f a Source #

minBound :: f a Source #

nan :: f a Source #

isNaN :: f a -> Bool Source #

(Naperian f, ExpField a) => ExpField (f a) Source # 

Methods

exp :: f a -> f a Source #

log :: f a -> f a Source #

logBase :: f a -> f a -> f a Source #

(**) :: f a -> f a -> f a Source #

sqrt :: f a -> f a Source #

(Naperian f, Field a) => Field (f a) Source # 
(Foldable f, Naperian f, Epsilon a) => Epsilon (f a) Source # 

Methods

nearZero :: f a -> Bool Source #

aboutEqual :: f a -> f a -> Bool Source #

(Naperian f, Signed a) => Signed (f a) Source # 

Methods

sign :: f a -> f a Source #

abs :: f a -> f a Source #

(Naperian f, Integral a) => Integral (f a) Source # 

Methods

div :: f a -> f a -> f a Source #

mod :: f a -> f a -> f a Source #

divMod :: f a -> f a -> (f a, f a) Source #

(Foldable f, Naperian f, ExpField a) => Metric (f a) a Source # 

Methods

distance :: f a -> f a -> a Source #

(Foldable f, Naperian f, ExpField a) => Normed (f a) a Source # 

Methods

size :: f a -> a Source #