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

Pandora.Paradigm.Inventory.Some.State

Synopsis

Documentation

newtype State s a Source #

Effectful computation with a variable

Constructors

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

Instances

Instances details
Zoomable State Exactly Source # 
Instance details

Defined in Pandora.Paradigm.Inventory

Methods

zoom :: forall bg ls (t :: Type -> Type). Adaptable t (->) (State bg) => Lens Exactly bg ls -> State (Simplification Exactly ls) ~> t Source #

Zoomable State Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Inventory

Methods

zoom :: forall bg ls (t :: Type -> Type). Adaptable t (->) (State bg) => Lens Maybe bg ls -> State (Simplification Maybe ls) ~> t Source #

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

Defined in Pandora.Paradigm.Inventory.Some.State

Methods

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

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

Defined in Pandora.Paradigm.Inventory.Some.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.Some.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 #

Gettable State Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.State

Associated Types

type Getting State e r Source #

Methods

get :: Getting State e r Source #

Settable State Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.State

Associated Types

type Setting State e r Source #

Methods

set :: Setting State e r Source #

Modifiable State Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.State

Associated Types

type Modification State e r Source #

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

Defined in Pandora.Paradigm.Inventory.Some.State

Methods

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

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

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

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

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

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

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

(<~~~~~~~~) :: ((->) < State s a) < Primary (State s) a Source #

(<~~~~~~~) :: ((->) < State s a) < Primary (State s) a Source #

(<~~~~~~) :: ((->) < State s a) < Primary (State s) a Source #

(<~~~~~) :: ((->) < State s a) < Primary (State s) a Source #

(<~~~~) :: ((->) < State s a) < Primary (State s) a Source #

(<~~~) :: ((->) < State s a) < Primary (State s) a Source #

(<~~) :: ((->) < State s a) < Primary (State s) a Source #

(<~) :: ((->) < State s a) < Primary (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 #

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

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

Defined in Pandora.Paradigm.Inventory.Some.State

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

Defined in Pandora.Paradigm.Inventory.Some.State

Methods

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

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

Defined in Pandora.Paradigm.Inventory.Some.State

Methods

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

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

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

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

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

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

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

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

(<-|-|-) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) (State s)) => (a -> b) -> State s (u a) -> State s (u b) Source #

(<-|-|--) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) (State s)) => (a -> b) -> State s (u a) -> State s (u b) Source #

(<-|-|---) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) (State s)) => (a -> b) -> State s (u a) -> State s (u b) Source #

(<-|-|----) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) (State s)) => (a -> b) -> State s (u a) -> State s (u b) Source #

(<-|-|-----) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) (State s)) => (a -> b) -> State s (u a) -> State s (u b) Source #

(<-|-|------) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) (State s)) => (a -> b) -> State s (u a) -> State s (u b) Source #

(<-|-|-------) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) (State s)) => (a -> b) -> State s (u a) -> State s (u b) Source #

(<-|-|-|-) :: (Covariant (->) (Betwixt (->) (Betwixt (->) (->))) v, Covariant (Betwixt (->) (Betwixt (->) (->))) (Betwixt (Betwixt (->) (->)) (->)) u, Covariant (Betwixt (Betwixt (->) (->)) (->)) (->) (State s)) => (a -> b) -> State s (u (v a)) -> State s (u (v 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 #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

type Schematic Monad (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.State

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

Defined in Pandora.Paradigm.Inventory.Some.State

type Primary (State s) a = (((->) s :: Type -> Type) :. (:*:) s) > a
type Getting State state ouput Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.State

type Getting State state ouput = State state state
type Setting State state output Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.State

type Setting State state output = state -> State state state
type Modification State state output Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.State

type Modification State state output = (state -> state) -> State state state

type Stateful s t = Adaptable t (->) (State s) Source #

reconcile :: (Bindable (->) t, Stateful s t, Adaptable t (->) u) => (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 #