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

Pandora.Paradigm.Inventory.State

Synopsis

Documentation

newtype State s a Source #

Effectful computation with a variable

Constructors

State (((->) s :. (:*:) s) := a) 

Instances

Instances details
Monoidal (-->) ((->) :: Type -> Type -> Type) (:*:) (:*:) (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

unit :: Proxy (:*:) -> (Unit (:*:) -> a) --> State s a Source #

Monadic (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

wrap :: forall (u :: Type -> Type). Pointable u => State s ~> (State s :> u) Source #

Semimonoidal (-->) (:*:) (:*:) (State s :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

mult :: forall (a :: k) (b :: k). (State s a :*: State s b) --> State s (a :*: b) Source #

Invariant (Flip State r) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

(<$<) :: (a -> b) -> (b -> a) -> Flip State r a -> Flip State r b Source #

invmap :: (a -> b) -> (b -> a) -> Flip State r a -> Flip State r b Source #

Bindable ((->) :: Type -> Type -> Type) (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

(=<<) :: (a -> State s b) -> State s a -> State s b Source #

Interpreted ((->) :: Type -> Type -> Type) (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Associated Types

type Primary (State s) a Source #

Methods

run :: State s a -> Primary (State s) a Source #

unite :: Primary (State s) a -> State s a Source #

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

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

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

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

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

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

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

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

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

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

Monad ((->) :: Type -> Type -> Type) (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

(<$>) :: (a -> b) -> State s a -> State s b Source #

Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Store s) (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory

Methods

(-|) :: (Store s a -> b) -> a -> State s b Source #

(|-) :: (a -> State s b) -> Store s a -> b Source #

type Schematic Monad (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

type Schematic Monad (State s) = ((->) s :: Type -> Type) <:<.>:> (:*:) s
type Primary (State s) a Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

type Primary (State s) a = (((->) s :: Type -> Type) :. (:*:) s) := a

current :: Stateful s t => t s Source #

Get current value

modify :: Stateful s t => (s -> s) -> t s Source #

Modify stored value with a function

replace :: Stateful s t => s -> t s Source #

Replace current value with another one

reconcile :: (Bindable (->) t, Stateful s t, Adaptable u t) => (s -> u s) -> t s Source #

type Memorable s t = (Covariant (->) (->) t, Pointable t, Stateful s t) Source #

fold :: (Traversable (->) (->) t, Memorable s u) => (a -> s -> s) -> t a -> u s Source #