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

Pandora.Pattern.Functor.Extendable

Synopsis

Documentation

class Covariant source source t => Extendable source t where Source #

When providing a new instance, you should ensure it satisfies:
* Duplication interchange: (f -<$$>-) . (identity <<=) ≡ (identity <<=) . (f <$>)
* Extension interchange: (f <<=) ≡ (f <$>) . (identity <<=)

Methods

(<<=) :: source (t a) b -> source (t a) (t b) infixr 1 Source #

Instances

Instances details
Extendable ((->) :: Type -> Type -> Type) Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

(<<=) :: (Identity a -> b) -> Identity a -> Identity b Source #

Extendable ((->) :: Type -> Type -> Type) (Proxy :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Proxy

Methods

(<<=) :: (Proxy a -> b) -> Proxy a -> Proxy b Source #

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

Defined in Pandora.Paradigm.Primary.Algebraic.Product

Methods

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

Extendable ((->) :: Type -> Type -> Type) t => Extendable ((->) :: Type -> Type -> Type) (Jack t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Jack

Methods

(<<=) :: (Jack t a -> b) -> Jack t a -> Jack t b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Extendable ((->) :: Type -> Type -> Type) (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

(<<=) :: (Construction t a -> b) -> Construction t a -> Construction t b Source #

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

Defined in Pandora.Paradigm.Inventory.Store

Methods

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

(Semimonoidal (<--) (:*:) (:*:) t, Extendable ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t) => Extendable ((->) :: Type -> Type -> Type) (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Methods

(<<=) :: (Tap t a -> b) -> Tap t a -> Tap t b Source #

Extendable ((->) :: Type -> Type -> Type) (Tap ((Stream <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Extendable ((->) :: Type -> Type -> Type) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(<<=) :: (Tap ((List <:.:> List) := (:*:)) a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

Semigroup e => Extendable ((->) :: Type -> Type -> Type) (Imprint e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

(<<=) :: (Imprint e a -> b) -> Imprint e a -> Imprint e b Source #

Extendable ((->) :: Type -> Type -> Type) (Equipment e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Equipment

Methods

(<<=) :: (Equipment e a -> b) -> Equipment e a -> Equipment e b Source #

(Extendable ((->) :: Type -> Type -> Type) t, Extendable ((->) :: Type -> Type -> Type) u) => Extendable ((->) :: Type -> Type -> Type) (Day t u) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Day

Methods

(<<=) :: (Day t u a -> b) -> Day t u a -> Day t u b Source #

Extendable ((->) :: Type -> Type -> Type) (Tagged tag) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

(<<=) :: (Tagged tag a -> b) -> Tagged tag a -> Tagged tag b Source #

Extendable ((->) :: Type -> Type -> Type) (Schematic Monad t u) => Extendable ((->) :: Type -> Type -> Type) (t :> u) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Monadic

Methods

(<<=) :: ((t :> u) a -> b) -> (t :> u) a -> (t :> u) b Source #

Extendable ((->) :: Type -> Type -> Type) (Schematic Comonad t u) => Extendable ((->) :: Type -> Type -> Type) (t :< u) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Comonadic

Methods

(<<=) :: ((t :< u) a -> b) -> (t :< u) a -> (t :< u) b Source #

(Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t' t, Extendable ((->) :: Type -> Type -> Type) u) => Extendable ((->) :: Type -> Type -> Type) ((t' <:<.>:> t) := u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

(<<=) :: (((t' <:<.>:> t) := u) a -> b) -> ((t' <:<.>:> t) := u) a -> ((t' <:<.>:> t) := u) b Source #

(Semigroup e, Extendable ((->) :: Type -> Type -> Type) u) => Extendable ((->) :: Type -> Type -> Type) (((->) e :: Type -> Type) <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

(<<=) :: (((->) e <.:> u) a -> b) -> ((->) e <.:> u) a -> ((->) e <.:> u) b Source #

Extendable ((->) :: Type -> Type -> Type) u => Extendable ((->) :: Type -> Type -> Type) ((:*:) e <:.> u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Equipment

Methods

(<<=) :: (((:*:) e <:.> u) a -> b) -> ((:*:) e <:.> u) a -> ((:*:) e <:.> u) b Source #