Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Documentation
class Interpreted t => Comonadic t where Source #
newtype (t :< u) a infixr 3 Source #
Instances
Hoistable (Schematic Comonad t) => Hoistable ((:<) t :: (Type -> Type) -> Type -> Type) Source # | |
(Lowering t (Schematic Comonad u (v :< (w :< (x :< (y :< (z :< (f :< h))))))), Lowering u (Schematic Comonad v (w :< (x :< (y :< (z :< (f :< h)))))), Lowering v (Schematic Comonad w (x :< (y :< (z :< (f :< h))))), Lowering w (Schematic Comonad x (y :< (z :< (f :< h)))), Lowering x (Schematic Comonad y (z :< (f :< h))), Lowering y (Schematic Comonad z (f :< h)), Lowering z (Schematic Comonad f h), Bringable f h) => Adaptable (t :< (u :< (v :< (w :< (x :< (y :< (z :< (f :< h))))))) :: Type -> Type) (f :: Type -> Type) Source # | |
(Lowering t (Schematic Comonad u (v :< (w :< (x :< (y :< (z :< (f :< h))))))), Lowering u (Schematic Comonad v (w :< (x :< (y :< (z :< (f :< h)))))), Lowering v (Schematic Comonad w (x :< (y :< (z :< (f :< h))))), Lowering w (Schematic Comonad x (y :< (z :< (f :< h)))), Lowering x (Schematic Comonad y (z :< (f :< h))), Lowering y (Schematic Comonad z (f :< h)), Lowering z (Schematic Comonad f h), Lowering f h) => Adaptable (t :< (u :< (v :< (w :< (x :< (y :< (z :< (f :< h))))))) :: Type -> Type) (h :: Type -> Type) Source # | |
(Lowering t (Schematic Comonad u (v :< (w :< (x :< (y :< (z :< f)))))), Lowering u (Schematic Comonad v (w :< (x :< (y :< (z :< f))))), Lowering v (Schematic Comonad w (x :< (y :< (z :< f)))), Lowering w (Schematic Comonad x (y :< (z :< f))), Lowering x (Schematic Comonad y (z :< f)), Lowering y (Schematic Comonad z f), Bringable z f) => Adaptable (t :< (u :< (v :< (w :< (x :< (y :< (z :< f)))))) :: Type -> Type) (z :: Type -> Type) Source # | |
(Lowering t (Schematic Comonad u (v :< (w :< (x :< (y :< (z :< f)))))), Lowering u (Schematic Comonad v (w :< (x :< (y :< (z :< f))))), Lowering v (Schematic Comonad w (x :< (y :< (z :< f)))), Lowering w (Schematic Comonad x (y :< (z :< f))), Lowering x (Schematic Comonad y (z :< f)), Lowering y (Schematic Comonad z f), Lowering z f) => Adaptable (t :< (u :< (v :< (w :< (x :< (y :< (z :< f)))))) :: Type -> Type) (f :: Type -> Type) Source # | |
(Lowering t (Schematic Comonad u (v :< (w :< (x :< (y :< z))))), Lowering u (Schematic Comonad v (w :< (x :< (y :< z)))), Lowering v (Schematic Comonad w (x :< (y :< z))), Lowering w (Schematic Comonad x (y :< z)), Lowering x (Schematic Comonad y z), Bringable y z) => Adaptable (t :< (u :< (v :< (w :< (x :< (y :< z))))) :: Type -> Type) (y :: Type -> Type) Source # | |
(Lowering t (Schematic Comonad u (v :< (w :< (x :< (y :< z))))), Lowering u (Schematic Comonad v (w :< (x :< (y :< z)))), Lowering v (Schematic Comonad w (x :< (y :< z))), Lowering w (Schematic Comonad x (y :< z)), Lowering x (Schematic Comonad y z), Lowering y z) => Adaptable (t :< (u :< (v :< (w :< (x :< (y :< z))))) :: Type -> Type) (z :: Type -> Type) Source # | |
(Lowering t (Schematic Comonad u (v :< (w :< (x :< y)))), Lowering u (Schematic Comonad v (w :< (x :< y))), Lowering v (Schematic Comonad w (x :< y)), Lowering w (Schematic Comonad x y), Bringable x y) => Adaptable (t :< (u :< (v :< (w :< (x :< y)))) :: Type -> Type) (x :: Type -> Type) Source # | |
(Lowering t (Schematic Comonad u (v :< (w :< (x :< y)))), Lowering u (Schematic Comonad v (w :< (x :< y))), Lowering v (Schematic Comonad w (x :< y)), Lowering w (Schematic Comonad x y), Lowering x y) => Adaptable (t :< (u :< (v :< (w :< (x :< y)))) :: Type -> Type) (y :: Type -> Type) Source # | |
(Lowering t (Schematic Comonad u (v :< (w :< x))), Lowering u (Schematic Comonad v (w :< x)), Lowering v (Schematic Comonad w x), Bringable w x) => Adaptable (t :< (u :< (v :< (w :< x))) :: Type -> Type) (w :: Type -> Type) Source # | |
(Lowering t (Schematic Comonad u (v :< (w :< x))), Lowering u (Schematic Comonad v (w :< x)), Lowering v (Schematic Comonad w x), Lowering w x) => Adaptable (t :< (u :< (v :< (w :< x))) :: Type -> Type) (x :: Type -> Type) Source # | |
(Lowering t (Schematic Comonad u v), Lowering t (Schematic Comonad u (v :< w)), Lowering u (Schematic Comonad v w), Lowering v w) => Adaptable (t :< (u :< (v :< w)) :: Type -> Type) (w :: Type -> Type) Source # | |
(Lowering t (Schematic Comonad u (v :< w)), Lowering u (Schematic Comonad v w), Bringable v w) => Adaptable (t :< (u :< (v :< w)) :: Type -> Type) (v :: Type -> Type) Source # | |
(Lowering t (Schematic Comonad u v), Lowering u v) => Adaptable (t :< (u :< v) :: Type -> Type) (v :: Type -> Type) Source # | |
(Lowering t (Schematic Comonad u v), Bringable u v) => Adaptable (t :< (u :< v) :: Type -> Type) (u :: Type -> Type) Source # | |
Bringable t u => Adaptable (t :< u :: Type -> Type) (t :: Type -> Type) Source # | |
Lowering t u => Adaptable (t :< u :: Type -> Type) (u :: Type -> Type) Source # | |
Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) (Schematic Comonad t u) => Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) (t :< u :: Type -> Type) Source # | |
Interpreted (Schematic Comonad t u) => Interpreted (t :< u) Source # | |
Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Comonadic run :: (t :< u) a -> Primary (t :< u) a Source # unite :: Primary (t :< u) a -> (t :< u) a Source # (||=) :: Interpreted u0 => (Primary (t :< u) a -> Primary u0 b) -> (t :< u) a -> u0 b Source # (=||) :: Interpreted u0 => ((t :< u) a -> u0 b) -> Primary (t :< u) a -> Primary u0 b Source # (<$||=) :: (Covariant (->) (->) j, Interpreted u0) => (Primary (t :< u) a -> Primary u0 b) -> (j := (t :< u) a) -> j := u0 b Source # (<$$||=) :: (Covariant (->) (->) j, Covariant (->) (->) k, Interpreted u0) => (Primary (t :< u) a -> Primary u0 b) -> ((j :. k) := (t :< u) a) -> (j :. k) := u0 b Source # (<$$$||=) :: (Covariant (->) (->) j, Covariant (->) (->) k, Covariant (->) (->) l, Interpreted u0) => (Primary (t :< u) a -> Primary u0 b) -> ((j :. (k :. l)) := (t :< u) a) -> (j :. (k :. l)) := u0 b Source # (<$$$$||=) :: (Covariant (->) (->) j, Covariant (->) (->) k, Covariant (->) (->) l, Covariant (->) (->) m, Interpreted u0) => (Primary (t :< u) a -> Primary u0 b) -> ((j :. (k :. (l :. m))) := (t :< u) a) -> (j :. (k :. (l :. m))) := u0 b Source # (=||$>) :: (Covariant (->) (->) j, Interpreted u0) => ((t :< u) a -> u0 b) -> (j := Primary (t :< u) a) -> j := Primary u0 b Source # (=||$$>) :: (Covariant (->) (->) j, Covariant (->) (->) k, Interpreted u0) => ((t :< u) a -> u0 b) -> ((j :. k) := Primary (t :< u) a) -> (j :. k) := Primary u0 b Source # (=||$$$>) :: (Covariant (->) (->) j, Covariant (->) (->) k, Covariant (->) (->) l, Interpreted u0) => ((t :< u) a -> u0 b) -> ((j :. (k :. l)) := Primary (t :< u) a) -> (j :. (k :. l)) := Primary u0 b Source # (=||$$$$>) :: (Covariant (->) (->) j, Covariant (->) (->) k, Covariant (->) (->) l, Covariant (->) (->) m, Interpreted u0) => ((t :< u) a -> u0 b) -> ((j :. (k :. (l :. m))) := Primary (t :< u) a) -> (j :. (k :. (l :. m))) := Primary u0 b Source # | |
Lowerable ((->) :: Type -> Type -> Type) (Schematic Comonad t) => Lowerable ((->) :: Type -> Type -> Type) ((:<) t) Source # | |
Extendable ((->) :: Type -> Type -> Type) (Schematic Comonad t u) => Extendable ((->) :: Type -> Type -> Type) (t :< u) Source # | |
Bindable ((->) :: Type -> Type -> Type) (Schematic Comonad t u) => Bindable ((->) :: Type -> Type -> Type) (t :< u) Source # | |
(Extractable_ (t :< u), Extendable ((->) :: Type -> Type -> Type) (t :< u)) => Comonad (t :< u) ((->) :: Type -> Type -> Type) Source # | |
Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) (Schematic Comonad t u) => Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) (t :< u) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Comonad t u) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t :< u) Source # | |
Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Comonad t u) => Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t :< u) Source # | |
Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Comonad t u) => Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t :< u) Source # | |
type Primary (t :< u) a Source # | |