Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Documentation
newtype TUT ct ct' cu t t' u a Source #
Instances
(Covariant t, Covariant t', Covariant u) => Covariant ((t <:<.>:> t') := u) Source # | |
Defined in Pandora.Paradigm.Schemes.TUT (<$>) :: (a -> b) -> ((t <:<.>:> t') := u) a -> ((t <:<.>:> t') := u) b Source # comap :: (a -> b) -> ((t <:<.>:> t') := u) a -> ((t <:<.>:> t') := u) b Source # (<$) :: a -> ((t <:<.>:> t') := u) b -> ((t <:<.>:> t') := u) a Source # ($>) :: ((t <:<.>:> t') := u) a -> b -> ((t <:<.>:> t') := u) b Source # void :: ((t <:<.>:> t') := u) a -> ((t <:<.>:> t') := u) () Source # loeb :: ((t <:<.>:> t') := u) (a <:= ((t <:<.>:> t') := u)) -> ((t <:<.>:> t') := u) a Source # (<&>) :: ((t <:<.>:> t') := u) a -> (a -> b) -> ((t <:<.>:> t') := u) b Source # (<$$>) :: Covariant u0 => (a -> b) -> ((((t <:<.>:> t') := u) :. u0) := a) -> (((t <:<.>:> t') := u) :. u0) := b Source # (<$$$>) :: (Covariant u0, Covariant v) => (a -> b) -> ((((t <:<.>:> t') := u) :. (u0 :. v)) := a) -> (((t <:<.>:> t') := u) :. (u0 :. v)) := b Source # (<$$$$>) :: (Covariant u0, Covariant v, Covariant w) => (a -> b) -> ((((t <:<.>:> t') := u) :. (u0 :. (v :. w))) := a) -> (((t <:<.>:> t') := u) :. (u0 :. (v :. w))) := b Source # (<&&>) :: Covariant u0 => ((((t <:<.>:> t') := u) :. u0) := a) -> (a -> b) -> (((t <:<.>:> t') := u) :. u0) := b Source # (<&&&>) :: (Covariant u0, Covariant v) => ((((t <:<.>:> t') := u) :. (u0 :. v)) := a) -> (a -> b) -> (((t <:<.>:> t') := u) :. (u0 :. v)) := b Source # (<&&&&>) :: (Covariant u0, Covariant v, Covariant w) => ((((t <:<.>:> t') := u) :. (u0 :. (v :. w))) := a) -> (a -> b) -> (((t <:<.>:> t') := u) :. (u0 :. (v :. w))) := b Source # (.#..) :: (((t <:<.>:> t') := u) ~ v a, Category v) => v c d -> ((v a :. v b) := c) -> (v a :. v b) := d Source # (.#...) :: (((t <:<.>:> t') := u) ~ v a, ((t <:<.>:> t') := u) ~ v b, Category v, Covariant (v a), Covariant (v b)) => v d e -> ((v a :. (v b :. v c)) := d) -> (v a :. (v b :. v c)) := e Source # (.#....) :: (((t <:<.>:> t') := u) ~ v a, ((t <:<.>:> t') := u) ~ v b, ((t <:<.>:> t') := u) ~ v c, Category v, Covariant (v a), Covariant (v b), Covariant (v c)) => v e f -> ((v a :. (v b :. (v c :. v d))) := e) -> (v a :. (v b :. (v c :. v d))) := f Source # (<$$) :: Covariant u0 => b -> ((((t <:<.>:> t') := u) :. u0) := a) -> (((t <:<.>:> t') := u) :. u0) := b Source # (<$$$) :: (Covariant u0, Covariant v) => b -> ((((t <:<.>:> t') := u) :. (u0 :. v)) := a) -> (((t <:<.>:> t') := u) :. (u0 :. v)) := b Source # (<$$$$) :: (Covariant u0, Covariant v, Covariant w) => b -> ((((t <:<.>:> t') := u) :. (u0 :. (v :. w))) := a) -> (((t <:<.>:> t') := u) :. (u0 :. (v :. w))) := b Source # ($$>) :: Covariant u0 => ((((t <:<.>:> t') := u) :. u0) := a) -> b -> (((t <:<.>:> t') := u) :. u0) := b Source # ($$$>) :: (Covariant u0, Covariant v) => ((((t <:<.>:> t') := u) :. (u0 :. v)) := a) -> b -> (((t <:<.>:> t') := u) :. (u0 :. v)) := b Source # ($$$$>) :: (Covariant u0, Covariant v, Covariant w) => ((((t <:<.>:> t') := u) :. (u0 :. (v :. w))) := a) -> b -> (((t <:<.>:> t') := u) :. (u0 :. (v :. w))) := b Source # | |
(Covariant t', Covariant t, Adjoint t' t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Extendable u ((->) :: Type -> Type -> Type)) => Extendable ((t' <:<.>:> t) := u) ((->) :: Type -> Type -> Type) 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 # | |
(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 # | |
(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 # | |
(forall (u :: Type -> Type). Covariant u, Adjoint t' t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Distributive t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Liftable (t <:<.>:> t') Source # | |
Defined in Pandora.Paradigm.Schemes.TUT | |
(forall (u :: Type -> Type). Covariant u, Adjoint t t' ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type), Distributive t' ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type)) => Lowerable (t <:<.>:> t') Source # | |
Defined in Pandora.Paradigm.Schemes.TUT | |
(Covariant ((t <:<.>:> u) t'), Covariant ((v <:<.>:> w) v'), 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 # | |
Interpreted (TUT ct ct' cu t t' u) Source # | |
Defined in Pandora.Paradigm.Schemes.TUT 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 # | |
type (>:<.>:<) = TUT Contravariant Covariant Contravariant infix 3 Source #
type (>:>.<:>) = TUT Contravariant Contravariant Covariant infix 3 Source #
type (<:>.<:<) = TUT Covariant Contravariant Contravariant infix 3 Source #
type (>:>.<:<) = TUT Contravariant Contravariant Contravariant infix 3 Source #