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

Pandora.Paradigm.Schemes.UT

Documentation

newtype UT ct cu t u a Source #

Constructors

UT ((u :. t) := a) 

Instances

Instances details
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) u) => Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) (t <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Semimonoidal (<--) (:*:) (:*:) t, Semimonoidal (<--) (:*:) (:*:) u) => Semimonoidal (<--) (:*:) (:*:) (t <.:> u :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

(Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Bindable ((->) :: Type -> Type -> Type) u) => Catchable e (Conclusion e <.:> u :: Type -> Type) Source # 
Instance details

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 ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) u) => Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) (t <.:> u :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) t, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) u) => Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) (t <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <.:> v), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (w <:.> u), Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v u, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t w) => Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <.:> v) (w <:.> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes

Methods

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

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

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <.:> v), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (w <.:> u), Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t u, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v w) => Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (t <.:> v) (w <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes

Methods

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

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

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (v <:.> t), Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (w <.:> u), Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t u, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) v w) => Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (v <:.> t) (w <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes

Methods

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

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

(Semigroup e, Extendable ((->) :: Type -> Type -> Type) u) => Extendable ((->) :: Type -> Type -> Type) (((->) e :: Type -> Type) <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

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

(Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Bindable ((->) :: Type -> Type -> Type) t, Semimonoidal ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Bindable ((->) :: Type -> Type -> Type) u) => Bindable ((->) :: Type -> Type -> Type) (t <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

Monoidal ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) t => Liftable ((->) :: Type -> Type -> Type) (UT Covariant Covariant t) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

lift :: Covariant (->) (->) u => u a -> UT Covariant Covariant t u a Source #

Monoidal (<--) ((->) :: Type -> Type -> Type) (:*:) (:*:) t => Lowerable ((->) :: Type -> Type -> Type) (UT Covariant Covariant t) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

lower :: Covariant (->) (->) u => UT Covariant Covariant t u a -> u a Source #

Interpreted (UT ct cu t u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Associated Types

type Primary (UT ct cu t u) a Source #

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 # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

type Primary (UT ct cu t u) a = (u :. t) := a