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

Pandora.Paradigm.Inventory.Some.Store

Synopsis

Documentation

newtype Store s a Source #

Context based computation on value

Constructors

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

Instances

Instances details
Monoidal (<--) (-->) (:*:) (:*:) (Store s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Store

Methods

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

Semigroupoid (Lens Exactly) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Methods

(.) :: Lens Exactly b c -> Lens Exactly a b -> Lens Exactly a c Source #

Semigroupoid (Lens Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Methods

(.) :: Lens Maybe b c -> Lens Maybe a b -> Lens Maybe a c Source #

Category (Lens Exactly) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Category (Lens Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

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

Defined in Pandora.Paradigm.Inventory.Some.Store

Methods

mult :: forall (a :: k) (b :: k). (Store s a :*: Store s b) <-- Store s (a :*: b) Source #

Semimonoidal (-->) (:*:) (:*:) (Lens Exactly source :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Methods

mult :: forall (a :: k) (b :: k). (Lens Exactly source a :*: Lens Exactly source b) --> Lens Exactly source (a :*: b) Source #

Impliable (P_Q_T ((->) :: Type -> Type -> Type) Store Exactly source target :: Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Associated Types

type Arguments (P_Q_T (->) Store Exactly source target) = (args :: Type) Source #

Methods

imply :: Arguments (P_Q_T (->) Store Exactly source target) Source #

Impliable (P_Q_T ((->) :: Type -> Type -> Type) Store Maybe source target :: Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Associated Types

type Arguments (P_Q_T (->) Store Maybe source target) = (args :: Type) Source #

Methods

imply :: Arguments (P_Q_T (->) Store Maybe source target) Source #

Invariant (Flip Store r) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Store

Methods

(<!<) :: (a -> b) -> (b -> a) -> Flip Store r a -> Flip Store r b Source #

invmap :: (a -> b) -> (b -> a) -> Flip Store r a -> Flip Store r b Source #

Invariant (Flip (Lens available) tgt) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Methods

(<!<) :: (a -> b) -> (b -> a) -> Flip (Lens available) tgt a -> Flip (Lens available) tgt b Source #

invmap :: (a -> b) -> (b -> a) -> Flip (Lens available) tgt a -> Flip (Lens available) tgt b Source #

Gettable (Lens Exactly) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Associated Types

type Getting (Lens Exactly) e r Source #

Methods

get :: Getting (Lens Exactly) e r Source #

Gettable (Lens Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Associated Types

type Getting (Lens Maybe) e r Source #

Methods

get :: Getting (Lens Maybe) e r Source #

Pointable t => Settable (Lens t :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Associated Types

type Setting (Lens t) e r Source #

Methods

set :: Setting (Lens t) e r Source #

(Gettable (Lens t), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Pointable t) => Modifiable (Lens t :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Associated Types

type Modification (Lens t) e r Source #

Methods

modify :: Modification (Lens t) e r Source #

Extendable ((->) :: Type -> Type -> Type) (Store s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Store

Methods

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

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

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

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

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

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

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

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

Interpreted ((->) :: Type -> Type -> Type) (Store s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Store

Associated Types

type Primary (Store s) a Source #

Methods

run :: ((->) < Store s a) < Primary (Store s) a Source #

unite :: ((->) < Primary (Store s) a) < Store s a Source #

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

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

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

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

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

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

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

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

(=#-) :: (Semigroupoid (->), Interpreted (->) u) => (((->) < Primary (Store s) a) < Primary u b) -> ((->) < Store s a) < u b Source #

(-#=) :: (Semigroupoid (->), Interpreted (->) u) => (((->) < Store s a) < u b) -> ((->) < Primary (Store s) a) < Primary u b Source #

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

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

Comonad ((->) :: Type -> Type -> Type) (Store s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Store

Comonadic ((->) :: Type -> Type -> Type) (Store s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Store

Methods

bring :: forall (u :: Type -> Type) a. Extractable u => ((->) < (Store s :< u) a) < Store s a Source #

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

Defined in Pandora.Paradigm.Inventory.Some.Store

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

(<-|-|-|-) :: (Covariant (->) (Betwixt (->) (Betwixt (->) (->))) v, Covariant (Betwixt (->) (Betwixt (->) (->))) (Betwixt (Betwixt (->) (->)) (->)) u, Covariant (Betwixt (Betwixt (->) (->)) (->)) (->) (Store s)) => (a -> b) -> Store s (u (v a)) -> Store 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 Comonad (Store s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Store

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

Defined in Pandora.Paradigm.Inventory.Some.Store

type Primary (Store s) a = ((:*:) s :. ((->) s :: Type -> Type)) >>> a
type Arguments (P_Q_T ((->) :: Type -> Type -> Type) Store Exactly source target :: Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

type Arguments (P_Q_T ((->) :: Type -> Type -> Type) Store Exactly source target :: Type) = (source -> target) -> (source -> target -> source) -> Lens Exactly source target
type Arguments (P_Q_T ((->) :: Type -> Type -> Type) Store Maybe source target :: Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

type Arguments (P_Q_T ((->) :: Type -> Type -> Type) Store Maybe source target :: Type) = (source -> Maybe target) -> (source -> Maybe target -> source) -> Lens Maybe source target
type Getting (Lens Exactly) source target Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

type Getting (Lens Exactly) source target = Lens Exactly source target -> source -> target
type Getting (Lens Maybe) source target Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

type Getting (Lens Maybe) source target = Lens Maybe source target -> source -> Maybe target
type Setting (Lens t :: Type -> Type -> Type) source target Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

type Setting (Lens t :: Type -> Type -> Type) source target = target -> Lens t source target -> source -> source
type Modification (Lens t :: Type -> Type -> Type) source target Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

type Modification (Lens t :: Type -> Type -> Type) source target = (target -> target) -> Lens t source target -> source -> source

type Storable s t = Adaptable (Store s) (->) t Source #

position :: Storable s t => t a -> s Source #

Get current index

look :: Storable s t => s -> a <:= t Source #

Given an index return value

retrofit :: (s -> s) -> Store s ~> Store s Source #

Change index with function