pandora-0.4.7: A box of patterns and paradigms
Safe HaskellSafe-Inferred
LanguageHaskell2010

Pandora.Paradigm.Inventory.Accumulator

Documentation

newtype Accumulator e a Source #

Constructors

Accumulator (e :*: a) 

Instances

Instances details
Monoid e => Monadic (Accumulator e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

wrap :: forall (u :: Type -> Type). Pointable u => Accumulator e ~> (Accumulator e :> u) Source #

Semigroup e => Semimonoidal (-->) (:*:) (:*:) (Accumulator e :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

mult :: forall (a :: k) (b :: k). (Accumulator e a :*: Accumulator e b) --> Accumulator e (a :*: b) Source #

Semigroup e => Bindable ((->) :: Type -> Type -> Type) (Accumulator e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

(=<<) :: (a -> Accumulator e b) -> Accumulator e a -> Accumulator e b Source #

Interpreted ((->) :: Type -> Type -> Type) (Accumulator e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Associated Types

type Primary (Accumulator e) a Source #

Methods

run :: Accumulator e a -> Primary (Accumulator e) a Source #

unite :: Primary (Accumulator e) a -> Accumulator e a Source #

(||=) :: (Semigroupoid (->), Interpreted (->) u) => (Primary (Accumulator e) a -> Primary u b) -> Accumulator e a -> u b Source #

(=||) :: (Semigroupoid (->), Interpreted (->) u) => (Accumulator e a -> u b) -> Primary (Accumulator e) a -> Primary u b Source #

(<$||=) :: (Semigroupoid (->), Covariant (->) (->) j, Interpreted (->) u) => (Primary (Accumulator e) a -> Primary u b) -> (j := Accumulator e a) -> (j := u b) Source #

(<$$||=) :: (Semigroupoid (->), Covariant (->) (->) j, Covariant (->) (->) k, Interpreted (->) u) => (Primary (Accumulator e) a -> Primary u b) -> ((j :. k) := Accumulator e a) -> ((j :. k) := u b) Source #

(<$$$||=) :: (Semigroupoid (->), Covariant (->) (->) j, Covariant (->) (->) k, Covariant (->) (->) l, Interpreted (->) u) => (Primary (Accumulator e) a -> Primary u b) -> ((j :. (k :. l)) := Accumulator e a) -> ((j :. (k :. l)) := u b) Source #

(<$$$$||=) :: (Semigroupoid (->), Covariant (->) (->) j, Covariant (->) (->) k, Covariant (->) (->) l, Covariant (->) (->) n, Interpreted (->) u) => (Primary (Accumulator e) a -> Primary u b) -> ((j :. (k :. (l :. n))) := Accumulator e a) -> ((j :. (k :. (l :. n))) := u b) Source #

(=||$>) :: (Covariant (->) (->) j, Interpreted (->) u) => (Accumulator e a -> u b) -> (j := Primary (Accumulator e) a) -> (j := Primary u b) Source #

(=||$$>) :: (Covariant (->) (->) j, Covariant (->) (->) k, Interpreted (->) u) => (Accumulator e a -> u b) -> ((j :. k) := Primary (Accumulator e) a) -> ((j :. k) := Primary u b) Source #

(=||$$$>) :: (Covariant (->) (->) j, Covariant (->) (->) k, Covariant (->) (->) l, Interpreted (->) u) => (Accumulator e a -> u b) -> ((j :. (k :. l)) := Primary (Accumulator e) a) -> ((j :. (k :. l)) := Primary u b) Source #

(=||$$$$>) :: (Covariant (->) (->) j, Covariant (->) (->) k, Covariant (->) (->) l, Covariant (->) (->) n, Interpreted (->) u) => (Accumulator e a -> u b) -> ((j :. (k :. (l :. n))) := Primary (Accumulator e) a) -> ((j :. (k :. (l :. n))) := Primary u b) Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Accumulator e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

(<$>) :: (a -> b) -> Accumulator e a -> Accumulator e b Source #

Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Accumulator e) (Imprint e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory

Methods

(-|) :: (Accumulator e a -> b) -> a -> Imprint e b Source #

(|-) :: (a -> Imprint e b) -> Accumulator e a -> b Source #

type Schematic Monad (Accumulator e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

type Primary (Accumulator e) a Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

type Primary (Accumulator e) a = e :*: a

gather :: Accumulated e t => e -> t () Source #