pandora-0.4.5: 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
Monad (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Interpreted (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 #

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

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

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

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

(<$$$||=) :: (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 #

(<$$$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Covariant m (->) (->), Interpreted u) => (Primary (State s) a -> Primary u b) -> ((j :. (k :. (l :. m))) := State s a) -> (j :. (k :. (l :. m))) := 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 m (->) (->), Interpreted u) => (State s a -> u b) -> ((j :. (k :. (l :. m))) := Primary (State s) a) -> (j :. (k :. (l :. m))) := Primary u b 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) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

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

Adjoint (Store s) (State s) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) 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 #

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

Defined in Pandora.Paradigm.Inventory.State

Methods

point :: a -> State s a Source #

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

Defined in Pandora.Paradigm.Inventory.State

Methods

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

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

Defined in Pandora.Paradigm.Inventory.State

Methods

(-<$>-) :: (a -> b) -> State s a -> State s 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 #

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 = (Pointable t (->), Semimonoidal t (->) (:*:) (:*:), Stateful s t) Source #

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