numhask-array-0.3: n-dimensional arrays

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

Associated Types

type Shape f Source #

Methods

shape :: f a -> Shape f Source #

Instances
Dimensions r => HasShape (Array c r) Source # 
Instance details

Defined in NumHask.Array

Associated Types

type Shape (Array c r) :: Type Source #

Methods

shape :: Array c r a -> Shape (Array c r) 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 :: Type -> Type) 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

Minimal complete definition

Nothing

Associated Types

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

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 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Par1 :: Type #

Methods

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

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

Representable Complex 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Complex :: Type #

Methods

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

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

Representable Identity 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Identity :: Type #

Methods

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

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

Representable Dual 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Dual :: Type #

Methods

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

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

Representable Sum 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Sum :: Type #

Methods

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

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

Representable Product 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Product :: Type #

Methods

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

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

Representable Range 
Instance details

Defined in NumHask.Data.Range

Associated Types

type Rep Range :: Type #

Methods

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

index :: Range a -> Rep Range -> a #

Representable (U1 :: Type -> Type) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep U1 :: Type #

Methods

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

index :: U1 a -> Rep U1 -> a #

Representable f => Representable (Co f) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Co f) :: Type #

Methods

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

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

Representable (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Proxy :: Type #

Methods

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

index :: Proxy a -> Rep Proxy -> a #

Representable f => Representable (Cofree f) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Cofree f) :: Type #

Methods

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

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

Representable f => Representable (Rec1 f) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Rec1 f) :: Type #

Methods

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

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

Representable w => Representable (TracedT s w) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (TracedT s w) :: Type #

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) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (IdentityT m) :: Type #

Methods

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

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

Representable (Tagged t) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Tagged t) :: Type #

Methods

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

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

Representable f => Representable (Reverse f) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Reverse f) :: Type #

Methods

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

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

Representable f => Representable (Backwards f) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Backwards f) :: Type #

Methods

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

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

Representable ((->) e :: Type -> Type) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep ((->) e) :: Type #

Methods

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

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

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

Defined in Data.Functor.Rep

Associated Types

type Rep (f :*: g) :: Type #

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) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Product f g) :: Type #

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) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (ReaderT e m) :: Type #

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 c r) Source # 
Instance details

Defined in NumHask.Array

Associated Types

type Rep (Array c r) :: Type #

Methods

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

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

Representable f => Representable (M1 i c f) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (M1 i c f) :: Type #

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) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (f :.: g) :: Type #

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) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (Compose f g) :: Type #

Methods

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

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