Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Pandora.Pattern.Functor.Extendable
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 # | |
Defined in Pandora.Paradigm.Basis.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 # | |
Defined in Pandora.Paradigm.Basis.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 # | |
Covariant t => Extendable (Twister t) Source # | |
Defined in Pandora.Paradigm.Basis.Twister Methods (=>>) :: Twister t a -> (Twister t a -> b) -> Twister t b Source # (<<=) :: (Twister t a -> b) -> Twister t a -> Twister t b Source # extend :: (Twister t a -> b) -> Twister t a -> Twister t b Source # duplicate :: Twister t a -> (Twister t :. Twister t) := a Source # (=<=) :: (Twister t b -> c) -> (Twister t a -> b) -> Twister t a -> c Source # (=>=) :: (Twister t a -> b) -> (Twister t b -> c) -> Twister t a -> c Source # | |
Extendable (Product a) Source # | |
Defined in Pandora.Paradigm.Basis.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 # | |
Extendable (Storage p) Source # | |
Defined in Pandora.Paradigm.Inventory.Storage Methods (=>>) :: Storage p a -> (Storage p a -> b) -> Storage p b Source # (<<=) :: (Storage p a -> b) -> Storage p a -> Storage p b Source # extend :: (Storage p a -> b) -> Storage p a -> Storage p b Source # duplicate :: Storage p a -> (Storage p :. Storage p) := a Source # (=<=) :: (Storage p b -> c) -> (Storage p a -> b) -> Storage p a -> c Source # (=>=) :: (Storage p a -> b) -> (Storage p b -> c) -> Storage p a -> c Source # | |
Extendable (Schema t u) => Extendable (t :> u) Source # | |
Defined in Pandora.Paradigm.Controlflow.Joint.Transformer 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 # | |
Defined in Pandora.Paradigm.Basis.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 # |