Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Pandora.Paradigm.Controlflow.Effect.Transformer.Monadic
Documentation
class Interpreted t => Monadic t where Source #
Instances
Monadic Maybe Source # | |
Monadic (Conclusion e) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Conclusion Methods wrap :: forall (u :: Type -> Type). Monoidal (->) (->) (:*:) (:*:) u => Conclusion e ~> (Conclusion e :> u) Source # | |
Monadic (State s) Source # | |
Monadic (Environment e) Source # | |
Defined in Pandora.Paradigm.Inventory.Environment Methods wrap :: forall (u :: Type -> Type). Monoidal (->) (->) (:*:) (:*:) u => Environment e ~> (Environment e :> u) Source # | |
Monoid e => Monadic (Accumulator e) Source # | |
Defined in Pandora.Paradigm.Inventory.Accumulator Methods wrap :: forall (u :: Type -> Type). Monoidal (->) (->) (:*:) (:*:) u => Accumulator e ~> (Accumulator e :> u) Source # |
newtype (t :> u) a infixr 3 Source #
Instances
(Lifting t (Schematic Monad u (v :> (w :> (x :> (y :> (z :> (f :> h))))))), Lifting u (Schematic Monad v (w :> (x :> (y :> (z :> (f :> h)))))), Lifting v (Schematic Monad w (x :> (y :> (z :> (f :> h))))), Lifting w (Schematic Monad x (y :> (z :> (f :> h)))), Lifting x (Schematic Monad y (z :> (f :> h))), Lifting y (Schematic Monad z (f :> h)), Lifting z (Schematic Monad f h), Wrappable f h) => Adaptable (f :: Type -> Type) (t :> (u :> (v :> (w :> (x :> (y :> (z :> (f :> h))))))) :: Type -> Type) Source # | |
(Lifting t (Schematic Monad u (v :> (w :> (x :> (y :> (z :> (f :> h))))))), Lifting u (Schematic Monad v (w :> (x :> (y :> (z :> (f :> h)))))), Lifting v (Schematic Monad w (x :> (y :> (z :> (f :> h))))), Lifting w (Schematic Monad x (y :> (z :> (f :> h)))), Lifting x (Schematic Monad y (z :> (f :> h))), Lifting y (Schematic Monad z (f :> h)), Lifting z (Schematic Monad f h), Lifting f h) => Adaptable (h :: Type -> Type) (t :> (u :> (v :> (w :> (x :> (y :> (z :> (f :> h))))))) :: Type -> Type) Source # | |
(Lifting t (Schematic Monad u (v :> (w :> (x :> (y :> (z :> f)))))), Lifting u (Schematic Monad v (w :> (x :> (y :> (z :> f))))), Lifting v (Schematic Monad w (x :> (y :> (z :> f)))), Lifting w (Schematic Monad x (y :> (z :> f))), Lifting x (Schematic Monad y (z :> f)), Lifting y (Schematic Monad z f), Wrappable z f) => Adaptable (z :: Type -> Type) (t :> (u :> (v :> (w :> (x :> (y :> (z :> f)))))) :: Type -> Type) Source # | |
(Lifting t (Schematic Monad u (v :> (w :> (x :> (y :> (z :> f)))))), Lifting u (Schematic Monad v (w :> (x :> (y :> (z :> f))))), Lifting v (Schematic Monad w (x :> (y :> (z :> f)))), Lifting w (Schematic Monad x (y :> (z :> f))), Lifting x (Schematic Monad y (z :> f)), Lifting y (Schematic Monad z f), Lifting z f) => Adaptable (f :: Type -> Type) (t :> (u :> (v :> (w :> (x :> (y :> (z :> f)))))) :: Type -> Type) Source # | |
(Lifting t (Schematic Monad u (v :> (w :> (x :> (y :> z))))), Lifting u (Schematic Monad v (w :> (x :> (y :> z)))), Lifting v (Schematic Monad w (x :> (y :> z))), Lifting w (Schematic Monad x (y :> z)), Lifting x (Schematic Monad y z), Wrappable y z) => Adaptable (y :: Type -> Type) (t :> (u :> (v :> (w :> (x :> (y :> z))))) :: Type -> Type) Source # | |
(Lifting t (Schematic Monad u (v :> (w :> (x :> (y :> z))))), Lifting u (Schematic Monad v (w :> (x :> (y :> z)))), Lifting v (Schematic Monad w (x :> (y :> z))), Lifting w (Schematic Monad x (y :> z)), Lifting x (Schematic Monad y z), Lifting y z) => Adaptable (z :: Type -> Type) (t :> (u :> (v :> (w :> (x :> (y :> z))))) :: Type -> Type) Source # | |
(Lifting t (Schematic Monad u (v :> (w :> (x :> y)))), Lifting u (Schematic Monad v (w :> (x :> y))), Lifting v (Schematic Monad w (x :> y)), Lifting w (Schematic Monad x y), Wrappable x y) => Adaptable (x :: Type -> Type) (t :> (u :> (v :> (w :> (x :> y)))) :: Type -> Type) Source # | |
(Lifting t (Schematic Monad u (v :> (w :> (x :> y)))), Lifting u (Schematic Monad v (w :> (x :> y))), Lifting v (Schematic Monad w (x :> y)), Lifting w (Schematic Monad x y), Lifting x y) => Adaptable (y :: Type -> Type) (t :> (u :> (v :> (w :> (x :> y)))) :: Type -> Type) Source # | |
(Lifting t (Schematic Monad u (v :> (w :> x))), Lifting u (Schematic Monad v (w :> x)), Lifting v (Schematic Monad w x), Wrappable w x) => Adaptable (w :: Type -> Type) (t :> (u :> (v :> (w :> x))) :: Type -> Type) Source # | |
(Lifting t (Schematic Monad u (v :> (w :> x))), Lifting u (Schematic Monad v (w :> x)), Lifting v (Schematic Monad w x), Lifting w x) => Adaptable (x :: Type -> Type) (t :> (u :> (v :> (w :> x))) :: Type -> Type) Source # | |
(Lifting t (Schematic Monad u v), Lifting t (Schematic Monad u (v :> w)), Lifting u (Schematic Monad v w), Lifting v w) => Adaptable (w :: Type -> Type) (t :> (u :> (v :> w)) :: Type -> Type) Source # | |
(Liftable ((->) :: Type -> Type -> Type) (Schematic Monad t), Lifting t (Schematic Monad u (v :> w)), Lifting u (Schematic Monad v w), Wrappable v w) => Adaptable (v :: Type -> Type) (t :> (u :> (v :> w)) :: Type -> Type) Source # | |
(Lifting t (Schematic Monad u v), Lifting u v) => Adaptable (v :: Type -> Type) (t :> (u :> v) :: Type -> Type) Source # | |
(Liftable ((->) :: Type -> Type -> Type) (Schematic Monad t), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad u v), Wrappable u v) => Adaptable (u :: Type -> Type) (t :> (u :> v) :: Type -> Type) Source # | |
Wrappable t u => Adaptable (t :: Type -> Type) (t :> u :: Type -> Type) Source # | |
Lifting t u => Adaptable (u :: Type -> Type) (t :> u :: Type -> Type) Source # | |
Hoistable (Schematic Monad t) => Hoistable ((:>) t :: (Type -> Type) -> Type -> Type) Source # | |
Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) (Schematic Monad t u) => Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) (t :> u :: Type -> Type) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) h, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad u (v :> (w :> (x :> (y :> (z :> (f :> h))))))), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad v (w :> (x :> (y :> (z :> (f :> h)))))), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad w (x :> (y :> (z :> (f :> h))))), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad x (y :> (z :> (f :> h)))), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad y (z :> (f :> h))), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad z (f :> h)), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad f h), Hoistable ((:>) (t :> (u :> (v :> w)))), Hoistable (Schematic Monad t), Hoistable (Schematic Monad u), Hoistable (Schematic Monad v), Hoistable (Schematic Monad w), Hoistable (Schematic Monad x), Hoistable (Schematic Monad y), Hoistable (Schematic Monad z), Hoistable (Schematic Monad f), Adaptable h h') => Adaptable (t :> (u :> (v :> (w :> (x :> (y :> (z :> (f :> h))))))) :: Type -> Type) (t :> (u :> (v :> (w :> (x :> (y :> (z :> (f :> h'))))))) :: Type -> Type) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) f, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad u (v :> (w :> (x :> (y :> (z :> f)))))), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad v (w :> (x :> (y :> (z :> f))))), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad w (x :> (y :> (z :> f)))), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad x (y :> (z :> f))), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad y (z :> f)), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad z f), Hoistable ((:>) (t :> (u :> (v :> w)))), Hoistable (Schematic Monad t), Hoistable (Schematic Monad u), Hoistable (Schematic Monad v), Hoistable (Schematic Monad w), Hoistable (Schematic Monad x), Hoistable (Schematic Monad y), Hoistable (Schematic Monad z), Adaptable f f') => Adaptable (t :> (u :> (v :> (w :> (x :> (y :> (z :> f)))))) :: Type -> Type) (t :> (u :> (v :> (w :> (x :> (y :> (z :> f')))))) :: Type -> Type) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) z, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad u (v :> (w :> (x :> (y :> z))))), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad v (w :> (x :> (y :> z)))), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad w (x :> (y :> z))), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad x (y :> z)), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad y z), Hoistable ((:>) (t :> (u :> (v :> w)))), Hoistable (Schematic Monad t), Hoistable (Schematic Monad u), Hoistable (Schematic Monad v), Hoistable (Schematic Monad w), Hoistable (Schematic Monad x), Hoistable (Schematic Monad y), Adaptable z z') => Adaptable (t :> (u :> (v :> (w :> (x :> (y :> z))))) :: Type -> Type) (t :> (u :> (v :> (w :> (x :> (y :> z'))))) :: Type -> Type) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) y, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad u (v :> (w :> (x :> y)))), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad v (w :> (x :> y))), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad w (x :> y)), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad x y), Hoistable ((:>) (t :> (u :> (v :> w)))), Hoistable (Schematic Monad t), Hoistable (Schematic Monad u), Hoistable (Schematic Monad v), Hoistable (Schematic Monad w), Hoistable (Schematic Monad x), Adaptable y y') => Adaptable (t :> (u :> (v :> (w :> (x :> y)))) :: Type -> Type) (t :> (u :> (v :> (w :> (x :> y')))) :: Type -> Type) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) x, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad u (v :> (w :> x))), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad v (w :> x)), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad w x), Hoistable ((:>) (t :> (u :> v))), Hoistable (Schematic Monad t), Hoistable (Schematic Monad u), Hoistable (Schematic Monad v), Hoistable (Schematic Monad w), Adaptable x x') => Adaptable (t :> (u :> (v :> (w :> x))) :: Type -> Type) (t :> (u :> (v :> (w :> x'))) :: Type -> Type) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) w, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad u v), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad u (v :> w)), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad v w), Hoistable ((:>) (t :> (u :> v))), Hoistable (Schematic Monad t), Hoistable (Schematic Monad u), Hoistable (Schematic Monad v), Adaptable w w') => Adaptable (t :> (u :> (v :> w)) :: Type -> Type) (t :> (u :> (v :> w')) :: Type -> Type) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad u v), Hoistable ((:>) (t :> u)), Hoistable (Schematic Monad t), Hoistable (Schematic Monad u), Adaptable v v') => Adaptable (t :> (u :> v) :: Type -> Type) (t :> (u :> v') :: Type -> Type) Source # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Hoistable ((:>) t), Adaptable u u') => Adaptable (t :> u :: Type -> Type) (t :> u' :: Type -> Type) Source # | |
Interpreted (Schematic Monad t u) => Interpreted (t :> u) Source # | |
Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Monadic Methods 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 # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad t u), Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) (Schematic Monad t u), Bindable ((->) :: Type -> Type -> Type) (t :> u)) => Monad (t :> u) Source # | |
Liftable ((->) :: Type -> Type -> Type) (Schematic Monad t) => Liftable ((->) :: Type -> Type -> Type) ((:>) t) Source # | |
Extendable ((->) :: Type -> Type -> Type) (Schematic Monad t u) => Extendable ((->) :: Type -> Type -> Type) (t :> u) Source # | |
Bindable ((->) :: Type -> Type -> Type) (Schematic Monad t u) => Bindable ((->) :: Type -> Type -> Type) (t :> u) Source # | |
Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) (Schematic Monad t u) => Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) (t :> u) Source # | |
Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad t u) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t :> u) Source # | |
Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad t u) => Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t :> u) Source # | |
Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad t u) => Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t :> u) Source # | |
type Primary (t :> u) a Source # | |