Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Pandora.Paradigm.Schemes.UT
Documentation
newtype UT ct cu t u a Source #
Instances
(Pointable u ((->) :: Type -> Type -> Type), Bindable u ((->) :: Type -> Type -> Type)) => Catchable e (Conclusion e <.:> u :: Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Conclusion Methods catch :: forall (a :: k). (Conclusion e <.:> u) a -> (e -> (Conclusion e <.:> u) a) -> (Conclusion e <.:> u) a Source # | |
(Covariant u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Semimonoidal t ((->) :: Type -> Type -> Type) (:*:) (:*:), Semimonoidal u ((->) :: Type -> Type -> Type) (:*:) (:*:)) => Semimonoidal (t <.:> u :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # | |
(Pointable t ((->) :: Type -> Type -> Type), Pointable u ((->) :: Type -> Type -> Type)) => Pointable (t <.:> u) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Schemes.UT | |
(Pointable u ((->) :: Type -> Type -> Type), Monoid e) => Pointable ((:*:) e <.:> u) ((->) :: Type -> Type -> Type) Source # | |
(Extractable t ((->) :: Type -> Type -> Type), Extractable u ((->) :: Type -> Type -> Type)) => Extractable (t <.:> u) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Schemes.UT | |
(Semigroup e, Extendable u ((->) :: Type -> Type -> Type)) => Extendable (((->) e :: Type -> Type) <.:> u) ((->) :: Type -> Type -> Type) Source # | |
(Traversable t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Bindable t ((->) :: Type -> Type -> Type), Semimonoidal u ((->) :: Type -> Type -> Type) (:*:) (:*:), Pointable u ((->) :: Type -> Type -> Type), Bindable u ((->) :: Type -> Type -> Type)) => Bindable (t <.:> u) ((->) :: Type -> Type -> Type) Source # | |
(Semigroup e, Pointable u ((->) :: Type -> Type -> Type), Bindable u ((->) :: Type -> Type -> Type)) => Bindable ((:*:) e <.:> u) ((->) :: Type -> Type -> Type) Source # | |
(Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Covariant (t <.:> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
(Covariant (t <.:> v) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant (w <:.> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint v u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t w ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Adjoint (t <.:> v) (w <:.> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
(Covariant (t <.:> v) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant (w <.:> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint v w ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Adjoint (t <.:> v) (w <.:> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
(Covariant (v <:.> t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant (w <.:> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint v w ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Adjoint (v <:.> t) (w <.:> u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Pointable t ((->) :: Type -> Type -> Type) => Liftable (UT Covariant Covariant t) Source # | |
Extractable t ((->) :: Type -> Type -> Type) => Lowerable (UT Covariant Covariant t) Source # | |
Interpreted (UT ct cu t u) Source # | |
Defined in Pandora.Paradigm.Schemes.UT Methods run :: UT ct cu t u a -> Primary (UT ct cu t u) a Source # unite :: Primary (UT ct cu t u) a -> UT ct cu t u a Source # (||=) :: Interpreted u0 => (Primary (UT ct cu t u) a -> Primary u0 b) -> UT ct cu t u a -> u0 b Source # (=||) :: Interpreted u0 => (UT ct cu t u a -> u0 b) -> Primary (UT ct cu t u) a -> Primary u0 b Source # (<$||=) :: (Covariant j (->) (->), Interpreted u0) => (Primary (UT ct cu t u) a -> Primary u0 b) -> (j := UT ct cu t u a) -> j := u0 b Source # (<$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Interpreted u0) => (Primary (UT ct cu t u) a -> Primary u0 b) -> ((j :. k) := UT ct cu t u a) -> (j :. k) := u0 b Source # (<$$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Interpreted u0) => (Primary (UT ct cu t u) a -> Primary u0 b) -> ((j :. (k :. l)) := UT ct cu t u a) -> (j :. (k :. l)) := u0 b Source # (<$$$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Covariant m (->) (->), Interpreted u0) => (Primary (UT ct cu t u) a -> Primary u0 b) -> ((j :. (k :. (l :. m))) := UT ct cu t u a) -> (j :. (k :. (l :. m))) := u0 b Source # (=||$>) :: (Covariant j (->) (->), Interpreted u0) => (UT ct cu t u a -> u0 b) -> (j := Primary (UT ct cu t u) a) -> j := Primary u0 b Source # (=||$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Interpreted u0) => (UT ct cu t u a -> u0 b) -> ((j :. k) := Primary (UT ct cu t u) a) -> (j :. k) := Primary u0 b Source # (=||$$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Interpreted u0) => (UT ct cu t u a -> u0 b) -> ((j :. (k :. l)) := Primary (UT ct cu t u) a) -> (j :. (k :. l)) := Primary u0 b Source # (=||$$$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Covariant m (->) (->), Interpreted u0) => (UT ct cu t u a -> u0 b) -> ((j :. (k :. (l :. m))) := Primary (UT ct cu t u) a) -> (j :. (k :. (l :. m))) := Primary u0 b Source # | |
type Primary (UT ct cu t u) a Source # | |
Defined in Pandora.Paradigm.Schemes.UT |
type (>.:<) = UT Contravariant Contravariant infixr 3 Source #