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

Pandora.Paradigm.Inventory.Store

Synopsis

Documentation

newtype Store s a Source #

Context based computation on value

Constructors

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

Instances

Instances details
Category (Lens Identity) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

Category (Lens Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Optics

Methods

identity :: Lens Maybe a a Source #

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

($) :: Lens Maybe (Lens Maybe a b) (Lens Maybe a b) Source #

(#) :: Lens Maybe (Lens Maybe a b) (Lens Maybe a b) Source #

Covariant (Store s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Store

Methods

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

comap :: (a -> b) -> Store s a -> Store s b Source #

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

($>) :: Store s a -> b -> Store s b Source #

void :: Store s a -> Store s () Source #

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

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

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

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

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

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

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

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

(.#..) :: (Store s ~ v a, Category v) => v c d -> ((v a :. v b) := c) -> (v a :. v b) := d Source #

(.#...) :: (Store s ~ v a, Store 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 #

(.#....) :: (Store s ~ v a, Store s ~ v b, Store 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 -> ((Store s :. u) := a) -> (Store s :. u) := b Source #

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

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

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

($$$>) :: (Covariant u, Covariant v) => ((Store s :. (u :. v)) := a) -> b -> (Store s :. (u :. v)) := b Source #

($$$$>) :: (Covariant u, Covariant v, Covariant w) => ((Store s :. (u :. (v :. w))) := a) -> b -> (Store s :. (u :. (v :. w))) := b Source #

Interpreted (Store s) Source # 
Instance details

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

(||=) :: Interpreted u => (Primary (Store s) a -> Primary u b) -> Store s a -> u b Source #

(=||) :: Interpreted u => (Store s a -> u b) -> Primary (Store s) a -> Primary u b Source #

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

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

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

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

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

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

(=||$$$>) :: (Covariant j, Covariant k, Covariant l, Interpreted u) => (Store s a -> u b) -> ((j :. (k :. l)) := Primary (Store s) a) -> (j :. (k :. l)) := Primary u b Source #

(=||$$$$>) :: (Covariant j, Covariant k, Covariant l, Covariant m, Interpreted u) => (Store s a -> u b) -> ((j :. (k :. (l :. m))) := Primary (Store s) a) -> (j :. (k :. (l :. m))) := Primary u b Source #

Comonadic (Store s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Store

Methods

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

Adjoint (Store s) (State s) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) 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 #

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

Defined in Pandora.Paradigm.Inventory.Store

Methods

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

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

Defined in Pandora.Paradigm.Inventory.Store

Methods

extract :: Store s a -> a Source #

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

Defined in Pandora.Paradigm.Inventory.Store

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

Defined in Pandora.Paradigm.Inventory.Store

Methods

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

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

Defined in Pandora.Paradigm.Inventory.Optics

Associated Types

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

Methods

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

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

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

type Primary (Store s) a Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Store

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

Defined in Pandora.Paradigm.Inventory.Optics

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

Defined in Pandora.Paradigm.Inventory.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 Schematic Comonad (Store s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Store

type Schematic Comonad (Store s) = (:*:) s <:<.>:> ((->) s :: Type -> Type)

type Storable s x = Adaptable x (Store s) 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