Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Documentation
class Interpreted m t => Monadic m t where Source #
Instances
Monadic ((->) :: Type -> Type -> Type) Maybe Source # | |
Monadic ((->) :: Type -> Type -> Type) (Conclusion e) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Conclusion wrap :: forall (u :: Type -> Type) a. Pointable u => Conclusion e a -> (Conclusion e :> u) a Source # | |
Monadic ((->) :: Type -> Type -> Type) (State s) Source # | |
Monadic ((->) :: Type -> Type -> Type) (Provision e) Source # | |
Monoid e => Monadic ((->) :: Type -> Type -> Type) (Accumulator e) Source # | |
Defined in Pandora.Paradigm.Inventory.Accumulator wrap :: forall (u :: Type -> Type) a. Pointable u => Accumulator e a -> (Accumulator e :> u) a Source # |
newtype (t :> u) a infixr 3 Source #
Instances
Monoidal (-->) (-->) (:*:) (:*:) (Schematic Monad t u) => Monoidal (-->) (-->) (:*:) (:*:) (t :> u) Source # | |
Semimonoidal (-->) (:*:) (:+:) (Schematic Monad t u) => Semimonoidal (-->) (:*:) (:+:) (t :> u :: Type -> Type) Source # | |
Semimonoidal (-->) (:*:) (:*:) (Schematic Monad t u) => Semimonoidal (-->) (:*:) (:*:) (t :> u :: Type -> Type) Source # | |
Effectful m v t u => Adaptable (t :> u :: Type -> Type) (m :: k -> Type -> Type) (v :: Type -> k) Source # | |
Hoistable ((->) :: Type -> Type -> Type) (Schematic Monad t) => Hoistable ((->) :: Type -> Type -> Type) ((:>) t :: (Type -> Type) -> Type -> Type) 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 # | |
Interpreted ((->) :: Type -> Type -> Type) (Schematic Monad t u) => Interpreted ((->) :: Type -> Type -> Type) (t :> u) Source # | |
Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Monadic 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 # (||=) :: (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 # | |
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Schematic Monad t u), Monoidal (-->) (-->) (:*:) (:*:) (Schematic Monad t u), Bindable ((->) :: Type -> Type -> Type) (t :> u)) => Monad ((->) :: 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 # | |
Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Monadic (<-|-) :: (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 (->) (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 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 # | |