Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
Covariant (State s) Source # | |
Defined in Pandora.Paradigm.Inventory.State (<$>) :: (a -> b) -> State s a -> State s b Source # comap :: (a -> b) -> State s a -> State s b Source # (<$) :: a -> State s b -> State s a Source # ($>) :: State s a -> b -> State s b Source # void :: State s a -> State s () Source # loeb :: State s (a <:= State s) -> State s a Source # (<&>) :: State s a -> (a -> b) -> State s b Source # (<$$>) :: Covariant u => (a -> b) -> ((State s :. u) := a) -> (State s :. u) := b Source # (<$$$>) :: (Covariant u, Covariant v) => (a -> b) -> ((State s :. (u :. v)) := a) -> (State s :. (u :. v)) := b Source # (<$$$$>) :: (Covariant u, Covariant v, Covariant w) => (a -> b) -> ((State s :. (u :. (v :. w))) := a) -> (State s :. (u :. (v :. w))) := b Source # (<&&>) :: Covariant u => ((State s :. u) := a) -> (a -> b) -> (State s :. u) := b Source # (<&&&>) :: (Covariant u, Covariant v) => ((State s :. (u :. v)) := a) -> (a -> b) -> (State s :. (u :. v)) := b Source # (<&&&&>) :: (Covariant u, Covariant v, Covariant w) => ((State s :. (u :. (v :. w))) := a) -> (a -> b) -> (State s :. (u :. (v :. w))) := b Source # (.#..) :: (State s ~ v a, Category v) => v c d -> ((v a :. v b) := c) -> (v a :. v b) := d Source # (.#...) :: (State s ~ v a, State s ~ v b, Category v, Covariant (v a), Covariant (v b)) => v d e -> ((v a :. (v b :. v c)) := d) -> (v a :. (v b :. v c)) := e Source # (.#....) :: (State s ~ v a, State s ~ v b, State s ~ v c, Category v, Covariant (v a), Covariant (v b), Covariant (v c)) => v e f -> ((v a :. (v b :. (v c :. v d))) := e) -> (v a :. (v b :. (v c :. v d))) := f Source # (<$$) :: Covariant u => b -> ((State s :. u) := a) -> (State s :. u) := b Source # (<$$$) :: (Covariant u, Covariant v) => b -> ((State s :. (u :. v)) := a) -> (State s :. (u :. v)) := b Source # (<$$$$) :: (Covariant u, Covariant v, Covariant w) => b -> ((State s :. (u :. (v :. w))) := a) -> (State s :. (u :. (v :. w))) := b Source # ($$>) :: Covariant u => ((State s :. u) := a) -> b -> (State s :. u) := b Source # ($$$>) :: (Covariant u, Covariant v) => ((State s :. (u :. v)) := a) -> b -> (State s :. (u :. v)) := b Source # ($$$$>) :: (Covariant u, Covariant v, Covariant w) => ((State s :. (u :. (v :. w))) := a) -> b -> (State s :. (u :. (v :. w))) := b Source # | |
Applicative (State s) Source # | |
Defined in Pandora.Paradigm.Inventory.State (<*>) :: State s (a -> b) -> State s a -> State s b Source # apply :: State s (a -> b) -> State s a -> State s b Source # (*>) :: State s a -> State s b -> State s b Source # (<*) :: State s a -> State s b -> State s a Source # forever :: State s a -> State s b Source # (<%>) :: State s a -> State s (a -> b) -> State s b Source # (<**>) :: Applicative u => ((State s :. u) := (a -> b)) -> ((State s :. u) := a) -> (State s :. u) := b Source # (<***>) :: (Applicative u, Applicative v) => ((State s :. (u :. v)) := (a -> b)) -> ((State s :. (u :. v)) := a) -> (State s :. (u :. v)) := b Source # (<****>) :: (Applicative u, Applicative v, Applicative w) => ((State s :. (u :. (v :. w))) := (a -> b)) -> ((State s :. (u :. (v :. w))) := a) -> (State s :. (u :. (v :. w))) := b Source # | |
Monad (State s) Source # | |
Defined in Pandora.Paradigm.Inventory.State | |
Interpreted (State s) Source # | |
Defined in Pandora.Paradigm.Inventory.State 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 -> Type) Source # | |
Adjoint (Store s) (State s) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Bindable (State s) ((->) :: Type -> Type -> Type) Source # | |
Pointable (State s) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Inventory.State | |
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 #