pandora-0.2.8: A box of patterns and paradigms

Safe HaskellSafe
LanguageHaskell2010

Pandora.Paradigm.Inventory.State

Contents

Documentation

newtype State s a Source #

Constructors

State (((->) s :. (:*:) s) := a) 
Instances
Interpreted (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Associated Types

type Primary (State s) a :: Type Source #

Methods

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

Covariant (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

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

Bindable (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

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

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

bind :: (a -> State s b) -> State s a -> State s b Source #

join :: ((State s :. State s) := a) -> State s a Source #

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

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

($>>=) :: Covariant u => (a -> State s b) -> ((u :. State s) := a) -> (u :. State s) := b Source #

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

Applicative (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

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

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

Pointable (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

point :: a |-> State s Source #

Monad (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Monadic (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Methods

lay :: Covariant u => u ~> (State s :> u) Source #

wrap :: Pointable u => State s ~> (State s :> u) Source #

Adjoint (Store s) (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory

Methods

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

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

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

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

eta :: a -> (State s :. Store s) := a Source #

epsilon :: ((Store s :. State s) := a) -> a Source #

type Schematic Monad (State s) u Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

type Schematic Monad (State s) u = TUT Covariant Covariant Covariant ((->) s :: Type -> Type) ((:*:) s) u
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 #

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

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

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

find :: (Pointable u, Avoidable u, Alternative u, Traversable t) => Predicate a -> t a -> u a Source #

Orphan instances

Covariant u => Covariant (TUT Covariant Covariant Covariant ((->) s :: Type -> Type) ((:*:) s) u) Source # 
Instance details

Methods

(<$>) :: (a -> b) -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b Source #

comap :: (a -> b) -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b Source #

(<$) :: a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a Source #

($>) :: TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> b -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b Source #

void :: TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u () Source #

loeb :: TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u (a <-| TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u) -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a Source #

(<&>) :: TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> (a -> b) -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b Source #

(<$$>) :: Covariant u0 => (a -> b) -> ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. u0) := a) -> (TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. u0) := b Source #

(<$$$>) :: (Covariant u0, Covariant v) => (a -> b) -> ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. v)) := a) -> (TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. v)) := b Source #

(<$$$$>) :: (Covariant u0, Covariant v, Covariant w) => (a -> b) -> ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. (v :. w))) := a) -> (TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. (v :. w))) := b Source #

(<&&>) :: Covariant u0 => ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. u0) := a) -> (a -> b) -> (TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. u0) := b Source #

(<&&&>) :: (Covariant u0, Covariant v) => ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. v)) := a) -> (a -> b) -> (TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. v)) := b Source #

(<&&&&>) :: (Covariant u0, Covariant v, Covariant w) => ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. (v :. w))) := a) -> (a -> b) -> (TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. (v :. w))) := b Source #

Bindable u => Bindable (TUT Covariant Covariant Covariant ((->) s :: Type -> Type) ((:*:) s) u) Source # 
Instance details

Methods

(>>=) :: TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> (a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b) -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b Source #

(=<<) :: (a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b) -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b Source #

bind :: (a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b) -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b Source #

join :: ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u) := a) -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a Source #

(>=>) :: (a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b) -> (b -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u c) -> a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u c Source #

(<=<) :: (b -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u c) -> (a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b) -> a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u c Source #

($>>=) :: Covariant u0 => (a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b) -> ((u0 :. TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u) := a) -> (u0 :. TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u) := b Source #

(>>=$) :: (TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b -> c) -> (a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b) -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> c Source #

Bindable u => Applicative (TUT Covariant Covariant Covariant ((->) s :: Type -> Type) ((:*:) s) u) Source # 
Instance details

Methods

(<*>) :: TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u (a -> b) -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b Source #

apply :: TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u (a -> b) -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b Source #

(*>) :: TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b Source #

(<*) :: TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a Source #

forever :: TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u a -> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u b Source #

(<**>) :: Applicative u0 => ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. u0) := (a -> b)) -> ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. u0) := a) -> (TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. u0) := b Source #

(<***>) :: (Applicative u0, Applicative v) => ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. v)) := (a -> b)) -> ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. v)) := a) -> (TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. v)) := b Source #

(<****>) :: (Applicative u0, Applicative v, Applicative w) => ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. (v :. w))) := (a -> b)) -> ((TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. (v :. w))) := a) -> (TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u :. (u0 :. (v :. w))) := b Source #

Pointable u => Pointable (TUT Covariant Covariant Covariant ((->) s :: Type -> Type) ((:*:) s) u) Source # 
Instance details

Methods

point :: a |-> TUT Covariant Covariant Covariant ((->) s) ((:*:) s) u Source #

Monad u => Monad (TUT Covariant Covariant Covariant ((->) s :: Type -> Type) ((:*:) s) u) Source # 
Instance details