numhask-array-0.1.1.0: See readme.md

Safe HaskellSafe
LanguageHaskell2010

NumHask.Shape

Contents

Description

numbers with a shape

Synopsis

Documentation

class HasShape f where Source #

Not everything that has a shape is representable.

todo: Structure is a useful alternative concept/naming convention

Minimal complete definition

shape

Associated Types

type Shape f Source #

Methods

shape :: f a -> Shape f Source #

Instances

Dimensions r => HasShape (Array Nat c r) Source # 

Associated Types

type Shape (Array Nat c r :: * -> *) :: * Source #

Methods

shape :: Array Nat c r a -> Shape (Array Nat c r) Source #

HasShape (Array XNat c xds) Source # 

Associated Types

type Shape (Array XNat c xds :: * -> *) :: * Source #

Methods

shape :: Array XNat c xds a -> Shape (Array XNat c xds) Source #

Representable

Representable has most of what's needed to define numbers that have elements (aka scalars) and a fixed shape.

class Distributive f => Representable (f :: * -> *) where #

A Functor f is Representable if tabulate and index witness an isomorphism to (->) x.

Every Distributive Functor is actually Representable.

Every Representable Functor from Hask to Hask is a right adjoint.

tabulate . index  ≡ id
index . tabulate  ≡ id
tabulate . returnreturn

Associated Types

type Rep (f :: * -> *) :: * #

If no definition is provided, this will default to GRep.

Methods

tabulate :: (Rep f -> a) -> f a #

fmap f . tabulatetabulate . fmap f

If no definition is provided, this will default to gtabulate.

index :: f a -> Rep f -> a #

If no definition is provided, this will default to gindex.

Instances

Representable Par1 

Associated Types

type Rep (Par1 :: * -> *) :: * #

Methods

tabulate :: (Rep Par1 -> a) -> Par1 a #

index :: Par1 a -> Rep Par1 -> a #

Representable Complex 

Associated Types

type Rep (Complex :: * -> *) :: * #

Methods

tabulate :: (Rep Complex -> a) -> Complex a #

index :: Complex a -> Rep Complex -> a #

Representable Identity 

Associated Types

type Rep (Identity :: * -> *) :: * #

Methods

tabulate :: (Rep Identity -> a) -> Identity a #

index :: Identity a -> Rep Identity -> a #

Representable Dual 

Associated Types

type Rep (Dual :: * -> *) :: * #

Methods

tabulate :: (Rep Dual -> a) -> Dual a #

index :: Dual a -> Rep Dual -> a #

Representable Sum 

Associated Types

type Rep (Sum :: * -> *) :: * #

Methods

tabulate :: (Rep Sum -> a) -> Sum a #

index :: Sum a -> Rep Sum -> a #

Representable Product 

Associated Types

type Rep (Product :: * -> *) :: * #

Methods

tabulate :: (Rep Product -> a) -> Product a #

index :: Product a -> Rep Product -> a #

Representable (U1 *) 

Associated Types

type Rep (U1 * :: * -> *) :: * #

Methods

tabulate :: (Rep (U1 *) -> a) -> U1 * a #

index :: U1 * a -> Rep (U1 *) -> a #

Representable f => Representable (Co f) 

Associated Types

type Rep (Co f :: * -> *) :: * #

Methods

tabulate :: (Rep (Co f) -> a) -> Co f a #

index :: Co f a -> Rep (Co f) -> a #

Representable (Proxy *) 

Associated Types

type Rep (Proxy * :: * -> *) :: * #

Methods

tabulate :: (Rep (Proxy *) -> a) -> Proxy * a #

index :: Proxy * a -> Rep (Proxy *) -> a #

Representable f => Representable (Cofree f) 

Associated Types

type Rep (Cofree f :: * -> *) :: * #

Methods

tabulate :: (Rep (Cofree f) -> a) -> Cofree f a #

index :: Cofree f a -> Rep (Cofree f) -> a #

Representable f => Representable (Rec1 * f) 

Associated Types

type Rep (Rec1 * f :: * -> *) :: * #

Methods

tabulate :: (Rep (Rec1 * f) -> a) -> Rec1 * f a #

index :: Rec1 * f a -> Rep (Rec1 * f) -> a #

Representable w => Representable (TracedT s w) 

Associated Types

type Rep (TracedT s w :: * -> *) :: * #

Methods

tabulate :: (Rep (TracedT s w) -> a) -> TracedT s w a #

index :: TracedT s w a -> Rep (TracedT s w) -> a #

Representable m => Representable (IdentityT * m) 

Associated Types

type Rep (IdentityT * m :: * -> *) :: * #

Methods

tabulate :: (Rep (IdentityT * m) -> a) -> IdentityT * m a #

index :: IdentityT * m a -> Rep (IdentityT * m) -> a #

Representable (Tagged * t) 

Associated Types

type Rep (Tagged * t :: * -> *) :: * #

Methods

tabulate :: (Rep (Tagged * t) -> a) -> Tagged * t a #

index :: Tagged * t a -> Rep (Tagged * t) -> a #

Representable f => Representable (Reverse * f) 

Associated Types

type Rep (Reverse * f :: * -> *) :: * #

Methods

tabulate :: (Rep (Reverse * f) -> a) -> Reverse * f a #

index :: Reverse * f a -> Rep (Reverse * f) -> a #

Representable f => Representable (Backwards * f) 

Associated Types

type Rep (Backwards * f :: * -> *) :: * #

Methods

tabulate :: (Rep (Backwards * f) -> a) -> Backwards * f a #

index :: Backwards * f a -> Rep (Backwards * f) -> a #

Representable ((->) LiftedRep LiftedRep e) 

Associated Types

type Rep ((LiftedRep -> LiftedRep) e :: * -> *) :: * #

Methods

tabulate :: (Rep ((LiftedRep -> LiftedRep) e) -> a) -> (LiftedRep -> LiftedRep) e a #

index :: (LiftedRep -> LiftedRep) e a -> Rep ((LiftedRep -> LiftedRep) e) -> a #

(Representable f, Representable g) => Representable ((:*:) * f g) 

Associated Types

type Rep ((* :*: f) g :: * -> *) :: * #

Methods

tabulate :: (Rep ((* :*: f) g) -> a) -> (* :*: f) g a #

index :: (* :*: f) g a -> Rep ((* :*: f) g) -> a #

(Representable f, Representable g) => Representable (Product * f g) 

Associated Types

type Rep (Product * f g :: * -> *) :: * #

Methods

tabulate :: (Rep (Product * f g) -> a) -> Product * f g a #

index :: Product * f g a -> Rep (Product * f g) -> a #

Representable m => Representable (ReaderT * e m) 

Associated Types

type Rep (ReaderT * e m :: * -> *) :: * #

Methods

tabulate :: (Rep (ReaderT * e m) -> a) -> ReaderT * e m a #

index :: ReaderT * e m a -> Rep (ReaderT * e m) -> a #

(Dimensions r, Container c) => Representable (Array Nat c r) # 

Associated Types

type Rep (Array Nat c r :: * -> *) :: * #

Methods

tabulate :: (Rep (Array Nat c r) -> a) -> Array Nat c r a #

index :: Array Nat c r a -> Rep (Array Nat c r) -> a #

Representable f => Representable (M1 * i c f) 

Associated Types

type Rep (M1 * i c f :: * -> *) :: * #

Methods

tabulate :: (Rep (M1 * i c f) -> a) -> M1 * i c f a #

index :: M1 * i c f a -> Rep (M1 * i c f) -> a #

(Representable f, Representable g) => Representable ((:.:) * * f g) 

Associated Types

type Rep ((* :.: *) f g :: * -> *) :: * #

Methods

tabulate :: (Rep ((* :.: *) f g) -> a) -> (* :.: *) f g a #

index :: (* :.: *) f g a -> Rep ((* :.: *) f g) -> a #

(Representable f, Representable g) => Representable (Compose * * f g) 

Associated Types

type Rep (Compose * * f g :: * -> *) :: * #

Methods

tabulate :: (Rep (Compose * * f g) -> a) -> Compose * * f g a #

index :: Compose * * f g a -> Rep (Compose * * f g) -> a #