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

Pandora.Paradigm.Controlflow.Effect.Transformer.Comonadic

Documentation

class Interpreted m t => Comonadic m t where Source #

Methods

bring :: Extractable u => (m < (t :< u) a) < t a Source #

Instances

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

Defined in Pandora.Paradigm.Inventory.Some.Store

Methods

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

newtype (t :< u) a infixr 3 Source #

Constructors

TC 

Fields

Instances

Instances details
Monoidal (-->) (-->) (:*:) (:*:) (Schematic Comonad t u) => Monoidal (-->) (-->) (:*:) (:*:) (t :< u) Source # 
Instance details

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

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) --> (t :< u) a Source #

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

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

Methods

mult :: forall (a :: k) (b :: k). ((t :< u) a :*: (t :< u) b) --> (t :< u) (a :*: b) Source #

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

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

Methods

(/|\) :: Covariant (->) (->) u => (forall a. u a -> v a) -> forall (a :: k). (t :< u) a -> (t :< v) a Source #

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

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

Methods

lower :: Covariant (->) (->) u => (t :< u) a -> u a 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 #

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

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

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

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

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

Associated Types

type Primary (t :< u) a Source #

Methods

run :: ((->) < (t :< u) a) < Primary (t :< u) a Source #

unite :: ((->) < Primary (t :< u) a) < (t :< u) a Source #

(<~~~~~~~~) :: ((->) < (t :< u) a) < Primary (t :< u) a Source #

(<~~~~~~~) :: ((->) < (t :< u) a) < Primary (t :< u) a Source #

(<~~~~~~) :: ((->) < (t :< u) a) < Primary (t :< u) a Source #

(<~~~~~) :: ((->) < (t :< u) a) < Primary (t :< u) a Source #

(<~~~~) :: ((->) < (t :< u) a) < Primary (t :< u) a Source #

(<~~~) :: ((->) < (t :< u) a) < Primary (t :< u) a Source #

(<~~) :: ((->) < (t :< u) a) < Primary (t :< u) a Source #

(<~) :: ((->) < (t :< u) a) < Primary (t :< u) a Source #

(=#-) :: (Semigroupoid (->), Interpreted (->) u0) => (((->) < Primary (t :< u) a) < Primary u0 b) -> ((->) < (t :< u) a) < u0 b Source #

(-#=) :: (Semigroupoid (->), Interpreted (->) u0) => (((->) < (t :< u) a) < u0 b) -> ((->) < Primary (t :< u) a) < Primary u0 b Source #

(<$=#-) :: (Semigroupoid (->), Covariant (->) (->) j, Interpreted (->) u0) => (((->) < Primary (t :< u) a) < Primary u0 b) -> (j > (t :< u) a) -> (j > u0 b) Source #

(-#=$>) :: (Covariant (->) (->) j, Interpreted (->) u0) => (((->) < (t :< u) a) < u0 b) -> (j > Primary (t :< u) a) -> (j > Primary u0 b) Source #

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

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

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

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

Methods

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

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

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

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

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

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

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

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

(<-|-|-) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) (t :< u)) => (a -> b) -> (t :< u) (u0 a) -> (t :< u) (u0 b) Source #

(<-|-|--) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) (t :< u)) => (a -> b) -> (t :< u) (u0 a) -> (t :< u) (u0 b) Source #

(<-|-|---) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) (t :< u)) => (a -> b) -> (t :< u) (u0 a) -> (t :< u) (u0 b) Source #

(<-|-|----) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) (t :< u)) => (a -> b) -> (t :< u) (u0 a) -> (t :< u) (u0 b) Source #

(<-|-|-----) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) (t :< u)) => (a -> b) -> (t :< u) (u0 a) -> (t :< u) (u0 b) Source #

(<-|-|------) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) (t :< u)) => (a -> b) -> (t :< u) (u0 a) -> (t :< u) (u0 b) Source #

(<-|-|-------) :: (Covariant (->) (Betwixt (->) (->)) u0, Covariant (Betwixt (->) (->)) (->) (t :< u)) => (a -> b) -> (t :< u) (u0 a) -> (t :< u) (u0 b) Source #

(<-|-|-|-) :: (Covariant (->) (Betwixt (->) (Betwixt (->) (->))) v, Covariant (Betwixt (->) (Betwixt (->) (->))) (Betwixt (Betwixt (->) (->)) (->)) u0, Covariant (Betwixt (Betwixt (->) (->)) (->)) (->) (t :< u)) => (a -> b) -> (t :< u) (u0 (v a)) -> (t :< u) (u0 (v b)) Source #

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

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

Methods

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

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

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

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

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

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

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

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

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

Methods

(<<-) :: (Covariant (->) (->) u0, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u0) => (a -> u0 b) -> (t :< u) a -> u0 ((t :< u) b) Source #

(<<-------) :: (Covariant (->) (->) u0, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u0) => (a -> u0 b) -> (t :< u) a -> u0 ((t :< u) b) Source #

(<<------) :: (Covariant (->) (->) u0, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u0) => (a -> u0 b) -> (t :< u) a -> u0 ((t :< u) b) Source #

(<<-----) :: (Covariant (->) (->) u0, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u0) => (a -> u0 b) -> (t :< u) a -> u0 ((t :< u) b) Source #

(<<----) :: (Covariant (->) (->) u0, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u0) => (a -> u0 b) -> (t :< u) a -> u0 ((t :< u) b) Source #

(<<---) :: (Covariant (->) (->) u0, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u0) => (a -> u0 b) -> (t :< u) a -> u0 ((t :< u) b) Source #

(<<--) :: (Covariant (->) (->) u0, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u0) => (a -> u0 b) -> (t :< u) a -> u0 ((t :< u) b) Source #

type Primary (t :< u) a Source # 
Instance details

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

type Primary (t :< u) a = Primary (Schematic Comonad t u) a