pandora-0.2.8: A box of patterns and paradigms

Safe HaskellSafe
LanguageHaskell2010

Pandora.Pattern.Functor.Extendable

Synopsis

Documentation

class Covariant t => Extendable t where Source #

When providing a new instance, you should ensure it satisfies the three laws:
* Duplication interchange: comap (comap f) . duplicate ≡ duplicate . comap f
* Extension interchange: extend f ≡ comap f . duplicate

Minimal complete definition

(=>>)

Methods

(=>>) :: t a -> (t a -> b) -> t b infixl 1 Source #

Infix and flipped version of extend, the dual of >>=

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

Flipped version of >>=, the dual of =<<

extend :: (t a -> b) -> t a -> t b Source #

Prefix and flipped version of =>>, the dual of bind

duplicate :: t a -> (t :. t) := a Source #

Clone existing structure, the dual of join

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

Right-to-left Cokleisli composition

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

Left-to-right Cokleisli composition

Instances
Extendable Identity Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Identity

Methods

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

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

extend :: (Identity a -> b) -> Identity a -> Identity b Source #

duplicate :: Identity a -> (Identity :. Identity) := a Source #

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

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

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

Defined in Pandora.Paradigm.Primary.Functor.Proxy

Methods

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

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

extend :: (Proxy a -> b) -> Proxy a -> Proxy b Source #

duplicate :: Proxy a -> (Proxy :. Proxy) := a Source #

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

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

Extendable (Product a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Product

Methods

(=>>) :: Product a a0 -> (Product a a0 -> b) -> Product a b Source #

(<<=) :: (Product a a0 -> b) -> Product a a0 -> Product a b Source #

extend :: (Product a a0 -> b) -> Product a a0 -> Product a b Source #

duplicate :: Product a a0 -> (Product a :. Product a) := a0 Source #

(=<=) :: (Product a b -> c) -> (Product a a0 -> b) -> Product a a0 -> c Source #

(=>=) :: (Product a a0 -> b) -> (Product a b -> c) -> Product a a0 -> c Source #

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

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

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

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

extend :: (Imprint e a -> b) -> Imprint e a -> Imprint e b Source #

duplicate :: Imprint e a -> (Imprint e :. Imprint e) := a Source #

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

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

Extendable (Store p) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Store

Methods

(=>>) :: Store p a -> (Store p a -> b) -> Store p b Source #

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

extend :: (Store p a -> b) -> Store p a -> Store p b Source #

duplicate :: Store p a -> (Store p :. Store p) := a Source #

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

(=>=) :: (Store p a -> b) -> (Store p b -> c) -> Store p a -> c Source #

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

Defined in Pandora.Paradigm.Primary.Transformer.Construction

Methods

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

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

extend :: (Construction t a -> b) -> Construction t a -> Construction t b Source #

duplicate :: Construction t a -> (Construction t :. Construction t) := a Source #

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

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

Extendable (Equipment e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Equipment

Methods

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

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

extend :: (Equipment e a -> b) -> Equipment e a -> Equipment e b Source #

duplicate :: Equipment e a -> (Equipment e :. Equipment e) := a Source #

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

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

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

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

Methods

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

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

extend :: ((t :> u) a -> b) -> (t :> u) a -> (t :> u) b Source #

duplicate :: (t :> u) a -> ((t :> u) :. (t :> u)) := a Source #

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

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

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

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

Methods

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

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

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

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

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

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

Extendable (Tagged tag) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Tagged

Methods

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

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

extend :: (Tagged tag a -> b) -> Tagged tag a -> Tagged tag b Source #

duplicate :: Tagged tag a -> (Tagged tag :. Tagged tag) := a Source #

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

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

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

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

(=>>) :: UT Covariant Covariant ((->) e) u a -> (UT Covariant Covariant ((->) e) u a -> b) -> UT Covariant Covariant ((->) e) u b Source #

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

extend :: (UT Covariant Covariant ((->) e) u a -> b) -> UT Covariant Covariant ((->) e) u a -> UT Covariant Covariant ((->) e) u b Source #

duplicate :: UT Covariant Covariant ((->) e) u a -> (UT Covariant Covariant ((->) e) u :. UT Covariant Covariant ((->) e) u) := a Source #

(=<=) :: (UT Covariant Covariant ((->) e) u b -> c) -> (UT Covariant Covariant ((->) e) u a -> b) -> UT Covariant Covariant ((->) e) u a -> c Source #

(=>=) :: (UT Covariant Covariant ((->) e) u a -> b) -> (UT Covariant Covariant ((->) e) u b -> c) -> UT Covariant Covariant ((->) e) u a -> c Source #

Extendable u => Extendable (TU Covariant Covariant ((:*:) e) u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Equipment

Extendable u => Extendable (TUT Covariant Covariant Covariant ((:*:) p) ((->) p :: Type -> Type) u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Store

Methods

(=>>) :: TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u a -> (TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u a -> b) -> TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u b Source #

(<<=) :: (TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u a -> b) -> TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u a -> TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u b Source #

extend :: (TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u a -> b) -> TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u a -> TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u b Source #

duplicate :: TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u a -> (TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u :. TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u) := a Source #

(=<=) :: (TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u b -> c) -> (TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u a -> b) -> TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u a -> c Source #

(=>=) :: (TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u a -> b) -> (TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u b -> c) -> TUT Covariant Covariant Covariant ((:*:) p) ((->) p) u a -> c Source #