pandora-0.4.4: 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
(Pointable u ((->) :: Type -> Type -> Type), Bindable u ((->) :: Type -> Type -> Type)) => 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 t, Covariant u) => Covariant (t <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

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

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

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

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

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

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

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

(<$$$>) :: (Covariant u0, Covariant v) => (a -> b) -> (((t <.:> u) :. (u0 :. v)) := a) -> ((t <.:> u) :. (u0 :. v)) := b Source #

(<$$$$>) :: (Covariant u0, Covariant v, Covariant w) => (a -> b) -> (((t <.:> u) :. (u0 :. (v :. w))) := a) -> ((t <.:> u) :. (u0 :. (v :. w))) := b Source #

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

(<&&&>) :: (Covariant u0, Covariant v) => (((t <.:> u) :. (u0 :. v)) := a) -> (a -> b) -> ((t <.:> u) :. (u0 :. v)) := b Source #

(<&&&&>) :: (Covariant u0, Covariant v, Covariant w) => (((t <.:> u) :. (u0 :. (v :. w))) := a) -> (a -> b) -> ((t <.:> u) :. (u0 :. (v :. w))) := b Source #

(.#..) :: ((t <.:> u) ~ v a, Category v) => v c d -> ((v a :. v b) := c) -> (v a :. v b) := d Source #

(.#...) :: ((t <.:> u) ~ v a, (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 <.:> u) ~ v a, (t <.:> u) ~ v b, (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 <.:> u) :. u0) := a) -> ((t <.:> u) :. u0) := b Source #

(<$$$) :: (Covariant u0, Covariant v) => b -> (((t <.:> u) :. (u0 :. v)) := a) -> ((t <.:> u) :. (u0 :. v)) := b Source #

(<$$$$) :: (Covariant u0, Covariant v, Covariant w) => b -> (((t <.:> u) :. (u0 :. (v :. w))) := a) -> ((t <.:> u) :. (u0 :. (v :. w))) := b Source #

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

($$$>) :: (Covariant u0, Covariant v) => (((t <.:> u) :. (u0 :. v)) := a) -> b -> ((t <.:> u) :. (u0 :. v)) := b Source #

($$$$>) :: (Covariant u0, Covariant v, Covariant w) => (((t <.:> u) :. (u0 :. (v :. w))) := a) -> b -> ((t <.:> u) :. (u0 :. (v :. w))) := b Source #

(Applicative t, Applicative u) => Applicative (t <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

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

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

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

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

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

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

(<***>) :: (Applicative u0, Applicative v) => (((t <.:> u) :. (u0 :. v)) := (a -> b)) -> (((t <.:> u) :. (u0 :. v)) := a) -> ((t <.:> u) :. (u0 :. v)) := b Source #

(<****>) :: (Applicative u0, Applicative v, Applicative w) => (((t <.:> u) :. (u0 :. (v :. w))) := (a -> b)) -> (((t <.:> u) :. (u0 :. (v :. w))) := a) -> ((t <.:> u) :. (u0 :. (v :. w))) := b Source #

(Semigroup e, Applicative u) => Applicative ((:*:) e <.:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

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

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

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

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

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

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

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

(<***>) :: (Applicative u0, Applicative v) => ((((:*:) e <.:> u) :. (u0 :. v)) := (a -> b)) -> ((((:*:) e <.:> u) :. (u0 :. v)) := a) -> (((:*:) e <.:> u) :. (u0 :. v)) := b Source #

(<****>) :: (Applicative u0, Applicative v, Applicative w) => ((((:*:) e <.:> u) :. (u0 :. (v :. w))) := (a -> b)) -> ((((:*:) e <.:> u) :. (u0 :. (v :. w))) := a) -> (((:*:) e <.:> u) :. (u0 :. (v :. w))) := b Source #

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

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

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

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

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

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

Defined in Pandora.Paradigm.Inventory.Imprint

Methods

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

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

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

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

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

(Pointable u ((->) :: Type -> Type -> Type), Monoid e) => Pointable ((:*:) e <.:> u) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Methods

point :: a -> ((:*:) e <.:> u) a 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 # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

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

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

Defined in Pandora.Paradigm.Schemes.UT

Methods

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

Extractable t ((->) :: Type -> Type -> Type) => Lowerable (UT Covariant Covariant t) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Methods

lower :: forall (u :: Type -> Type). Covariant_ u (->) (->) => UT Covariant Covariant t u ~> u 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