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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

(Adjoint t' t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Extendable u ((->) :: Type -> Type -> Type)) => Extendable ((t' <:<.>:> t) := u) ((->) :: Type -> Type -> Type) 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 t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant t' ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant u ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Covariant ((t <:<.>:> t') := u) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

lift :: forall (u :: Type -> Type). Covariant u (->) (->) => u ~> (t <:<.>:> t') u Source #

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

Defined in Pandora.Paradigm.Schemes.TUT

Methods

lower :: forall (u :: Type -> Type). Covariant u (->) (->) => (t <:<.>:> t') u ~> u Source #

(Covariant ((t <:<.>:> u) t') ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Covariant ((v <:<.>:> w) v') ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t w ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t' v' ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint t v ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint u v ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Adjoint v' t' ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Adjoint ((t <:<.>:> u) t') ((v <:<.>:> w) v') ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) 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 #

Interpreted (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 #

(||=) :: 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 #

(=||) :: 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 #

(<$||=) :: (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 #

(<$$||=) :: (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 #

(<$$$||=) :: (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 #

(<$$$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Covariant m (->) (->), Interpreted u0) => (Primary (TUT ct ct' cu t t' u) a -> Primary u0 b) -> ((j :. (k :. (l :. m))) := TUT ct ct' cu t t' u a) -> (j :. (k :. (l :. m))) := 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 m (->) (->), Interpreted u0) => (TUT ct ct' cu t t' u a -> u0 b) -> ((j :. (k :. (l :. m))) := Primary (TUT ct ct' cu t t' u) a) -> (j :. (k :. (l :. m))) := 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