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

Pandora.Paradigm.Schemes.P_Q_T

Documentation

newtype P_Q_T (p :: * -> * -> *) (q :: * -> * -> *) (t :: * -> *) (a :: *) (b :: *) Source #

Constructors

P_Q_T (p a (q (t b) 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 #

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 (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 #

Interpreted (P_Q_T p q t a) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.P_Q_T

Associated Types

type Primary (P_Q_T p q t a) a Source #

Methods

run :: P_Q_T p q t a a0 -> Primary (P_Q_T p q t a) a0 Source #

unite :: Primary (P_Q_T p q t a) a0 -> P_Q_T p q t a a0 Source #

(||=) :: Interpreted u => (Primary (P_Q_T p q t a) a0 -> Primary u b) -> P_Q_T p q t a a0 -> u b Source #

(=||) :: Interpreted u => (P_Q_T p q t a a0 -> u b) -> Primary (P_Q_T p q t a) a0 -> Primary u b Source #

(<$||=) :: (Covariant j, Interpreted u) => (Primary (P_Q_T p q t a) a0 -> Primary u b) -> (j := P_Q_T p q t a a0) -> j := u b Source #

(<$$||=) :: (Covariant j, Covariant k, Interpreted u) => (Primary (P_Q_T p q t a) a0 -> Primary u b) -> ((j :. k) := P_Q_T p q t a a0) -> (j :. k) := u b Source #

(<$$$||=) :: (Covariant j, Covariant k, Covariant l, Interpreted u) => (Primary (P_Q_T p q t a) a0 -> Primary u b) -> ((j :. (k :. l)) := P_Q_T p q t a a0) -> (j :. (k :. l)) := u b Source #

(<$$$$||=) :: (Covariant j, Covariant k, Covariant l, Covariant m, Interpreted u) => (Primary (P_Q_T p q t a) a0 -> Primary u b) -> ((j :. (k :. (l :. m))) := P_Q_T p q t a a0) -> (j :. (k :. (l :. m))) := u b Source #

(=||$>) :: (Covariant j, Interpreted u) => (P_Q_T p q t a a0 -> u b) -> (j := Primary (P_Q_T p q t a) a0) -> j := Primary u b Source #

(=||$$>) :: (Covariant j, Covariant k, Interpreted u) => (P_Q_T p q t a a0 -> u b) -> ((j :. k) := Primary (P_Q_T p q t a) a0) -> (j :. k) := Primary u b Source #

(=||$$$>) :: (Covariant j, Covariant k, Covariant l, Interpreted u) => (P_Q_T p q t a a0 -> u b) -> ((j :. (k :. l)) := Primary (P_Q_T p q t a) a0) -> (j :. (k :. l)) := Primary u b Source #

(=||$$$$>) :: (Covariant j, Covariant k, Covariant l, Covariant m, Interpreted u) => (P_Q_T p q t a a0 -> u b) -> ((j :. (k :. (l :. m))) := Primary (P_Q_T p q t a) a0) -> (j :. (k :. (l :. m))) := Primary u b Source #

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 Primary (P_Q_T p q t a) b Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.P_Q_T

type Primary (P_Q_T p q t a) b = p a (q (t b) a)