Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Pandora.Paradigm.Inventory.State
Synopsis
- newtype State s a = State (((->) s :. (:*:) s) := a)
- type Stateful s = Adaptable (State s)
- current :: Stateful s t => t s
- modify :: Stateful s t => (s -> s) -> t s
- replace :: Stateful s t => s -> t s
- reconcile :: (Bindable t (->), Stateful s t, Adaptable u t) => (s -> u s) -> t s
- type Memorable s t = (Pointable t (->), Semimonoidal t (->) (:*:) (:*:), Stateful s t)
- fold :: (Traversable t (->) (->), Memorable s u) => (a -> s -> s) -> t a -> u s
Documentation
Effectful computation with a variable
Instances
Monad (State s) Source # | |
Defined in Pandora.Paradigm.Inventory.State | |
Interpreted (State s) Source # | |
Defined in Pandora.Paradigm.Inventory.State 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 # | |
Semimonoidal (State s :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
Adjoint (Store s) (State s) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Pointable (State s) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Inventory.State | |
Bindable (State s) ((->) :: Type -> Type -> Type) Source # | |
Covariant (State s) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Invariant (Flip State r) Source # | |
type Schematic Monad (State s) Source # | |
type Primary (State s) a Source # | |
fold :: (Traversable t (->) (->), Memorable s u) => (a -> s -> s) -> t a -> u s Source #