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

Pandora.Paradigm.Schemes.TUT

Documentation

newtype TUT ct ct' cu t t' u a Source #

Constructors

TUT ((t :. (u :. t')) := a) 

Instances

Instances details
(Covariant m m t, Covariant m m u, Covariant m m t', Interpreted m ((t <:<.>:> t') := u)) => Covariant m m ((t <:<.>:> t') := u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

(<$>) :: m a b -> m (((t <:<.>:> t') := u) a) (((t <:<.>:> t') := u) b) 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', Semimonoidal (-->) (:*:) (:*:) t, Semimonoidal (-->) (:*:) (:*:) t', Monoidal (-->) ((->) :: Type -> Type -> Type) (:*:) (:*:) u, Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t' t) => Monoidal (-->) ((->) :: Type -> Type -> Type) (:*:) (:*:) ((t <:<.>:> t') := u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes

Methods

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

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

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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

(Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t' t, Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t) => Liftable ((->) :: Type -> Type -> Type) (t <:<.>:> t') Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

lift :: Covariant (->) (->) u => u a -> (t <:<.>:> t') u a Source #

(Adjoint ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t t', Distributive ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t') => Lowerable ((->) :: Type -> Type -> Type) (t <:<.>:> t') Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

lower :: Covariant (->) (->) u => (t <:<.>:> t') u a -> u a Source #

Interpreted ((->) :: Type -> Type -> Type) (TUT ct ct' cu t t' u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Associated Types

type Primary (TUT ct ct' cu t t' u) a Source #

Methods

run :: TUT ct ct' cu t t' u a -> Primary (TUT ct ct' cu t t' u) a Source #

unite :: Primary (TUT ct ct' cu t t' u) a -> TUT ct ct' cu t t' u a Source #

(||=) :: (Semigroupoid (->), Interpreted (->) u0) => (Primary (TUT ct ct' cu t t' u) a -> Primary u0 b) -> TUT ct ct' cu t t' u a -> u0 b Source #

(=||) :: (Semigroupoid (->), Interpreted (->) u0) => (TUT ct ct' cu t t' u a -> u0 b) -> Primary (TUT ct ct' cu t t' u) a -> Primary u0 b Source #

(<$||=) :: (Semigroupoid (->), Covariant (->) (->) j, Interpreted (->) u0) => (Primary (TUT ct ct' cu t t' u) a -> Primary u0 b) -> (j := TUT ct ct' cu t t' u a) -> (j := u0 b) Source #

(<$$||=) :: (Semigroupoid (->), Covariant (->) (->) j, Covariant (->) (->) k, Interpreted (->) u0) => (Primary (TUT ct ct' cu t t' u) a -> Primary u0 b) -> ((j :. k) := TUT ct ct' cu t t' u a) -> ((j :. k) := u0 b) Source #

(<$$$||=) :: (Semigroupoid (->), Covariant (->) (->) j, Covariant (->) (->) k, Covariant (->) (->) l, Interpreted (->) u0) => (Primary (TUT ct ct' cu t t' u) a -> Primary u0 b) -> ((j :. (k :. l)) := TUT ct ct' cu t t' u a) -> ((j :. (k :. l)) := u0 b) Source #

(<$$$$||=) :: (Semigroupoid (->), Covariant (->) (->) j, Covariant (->) (->) k, Covariant (->) (->) l, Covariant (->) (->) n, Interpreted (->) u0) => (Primary (TUT ct ct' cu t t' u) a -> Primary u0 b) -> ((j :. (k :. (l :. n))) := TUT ct ct' cu t t' u a) -> ((j :. (k :. (l :. n))) := u0 b) Source #

(=||$>) :: (Covariant (->) (->) j, Interpreted (->) u0) => (TUT ct ct' cu t t' u a -> u0 b) -> (j := Primary (TUT ct ct' cu t t' u) a) -> (j := Primary u0 b) Source #

(=||$$>) :: (Covariant (->) (->) j, Covariant (->) (->) k, Interpreted (->) u0) => (TUT ct ct' cu t t' u a -> u0 b) -> ((j :. k) := Primary (TUT ct ct' cu t t' u) a) -> ((j :. k) := Primary u0 b) Source #

(=||$$$>) :: (Covariant (->) (->) j, Covariant (->) (->) k, Covariant (->) (->) l, Interpreted (->) u0) => (TUT ct ct' cu t t' u a -> u0 b) -> ((j :. (k :. l)) := Primary (TUT ct ct' cu t t' u) a) -> ((j :. (k :. l)) := Primary u0 b) Source #

(=||$$$$>) :: (Covariant (->) (->) j, Covariant (->) (->) k, Covariant (->) (->) l, Covariant (->) (->) n, Interpreted (->) u0) => (TUT ct ct' cu t t' u a -> u0 b) -> ((j :. (k :. (l :. n))) := Primary (TUT ct ct' cu t t' u) a) -> ((j :. (k :. (l :. n))) := Primary u0 b) Source #

type Primary (TUT ct ct' cu t t' u) a Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

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