pandora-0.1.9: A box of patterns and paradigms

Safe HaskellSafe
LanguageHaskell2010

Pandora.Pattern.Junction.Schemes.UTU

Documentation

newtype UTU ct cu t u a Source #

Constructors

UTU ((u :.: t u) >< a) 
Instances
(forall (u' :: Type -> Type). Pointable u', Liftable t) => Liftable (UTU Co Co t) Source # 
Instance details

Defined in Pandora.Pattern.Junction.Schemes.UTU

Methods

lift :: Covariant u => u ~> UTU Co Co t u Source #

(forall (u' :: Type -> Type). Extractable u', Lowerable t) => Lowerable (UTU Co Co t) Source # 
Instance details

Defined in Pandora.Pattern.Junction.Schemes.UTU

Methods

lower :: Covariant u => UTU Co Co t u ~> u Source #

(Covariant (t u), Covariant u) => Covariant (UTU Co Co t u) Source # 
Instance details

Defined in Pandora.Pattern.Junction.Schemes.UTU

Methods

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

comap :: (a -> b) -> UTU Co Co t u a -> UTU Co Co t u b Source #

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

($>) :: UTU Co Co t u a -> b -> UTU Co Co t u b Source #

void :: UTU Co Co t u a -> UTU Co Co t u () Source #

loeb :: UTU Co Co t u (UTU Co Co t u a -> a) -> UTU Co Co t u a Source #

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

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

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

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

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

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

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

(Applicative (t u), Applicative u) => Applicative (UTU Co Co t u) Source # 
Instance details

Defined in Pandora.Pattern.Junction.Schemes.UTU

Methods

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

apply :: UTU Co Co t u (a -> b) -> UTU Co Co t u a -> UTU Co Co t u b Source #

(*>) :: UTU Co Co t u a -> UTU Co Co t u b -> UTU Co Co t u b Source #

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

forever :: UTU Co Co t u a -> UTU Co Co t u b Source #

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

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

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

(Covariant (t u), Alternative u) => Alternative (UTU Co Co t u) Source # 
Instance details

Defined in Pandora.Pattern.Junction.Schemes.UTU

Methods

(<+>) :: UTU Co Co t u a -> UTU Co Co t u a -> UTU Co Co t u a Source #

alter :: UTU Co Co t u a -> UTU Co Co t u a -> UTU Co Co t u a Source #

(Covariant (t u), Avoidable u) => Avoidable (UTU Co Co t u) Source # 
Instance details

Defined in Pandora.Pattern.Junction.Schemes.UTU

Methods

empty :: UTU Co Co t u a Source #

(Distributive (t u), Distributive u) => Distributive (UTU Co Co t u) Source # 
Instance details

Defined in Pandora.Pattern.Junction.Schemes.UTU

Methods

(>>-) :: Covariant t0 => t0 a -> (a -> UTU Co Co t u b) -> (UTU Co Co t u :.: t0) >< b Source #

collect :: Covariant t0 => (a -> UTU Co Co t u b) -> t0 a -> (UTU Co Co t u :.: t0) >< b Source #

distribute :: Covariant t0 => ((t0 :.: UTU Co Co t u) >< a) -> (UTU Co Co t u :.: t0) >< a Source #

(>>>-) :: (Covariant t0, Covariant v) => ((t0 :.: v) >< a) -> (a -> UTU Co Co t u b) -> (UTU Co Co t u :.: (t0 :.: v)) >< b Source #

(>>>>-) :: (Covariant t0, Covariant v, Covariant w) => ((t0 :.: (v :.: w)) >< a) -> (a -> UTU Co Co t u b) -> (UTU Co Co t u :.: (t0 :.: (v :.: w))) >< b Source #

(>>>>>-) :: (Covariant t0, Covariant v, Covariant w, Covariant j) => ((t0 :.: (v :.: (w :.: j))) >< a) -> (a -> UTU Co Co t u b) -> (UTU Co Co t u :.: (t0 :.: (v :.: (w :.: j)))) >< b Source #

(Extractable (t u), Extractable u) => Extractable (UTU Co Co t u) Source # 
Instance details

Defined in Pandora.Pattern.Junction.Schemes.UTU

Methods

extract :: UTU Co Co t u a -> a Source #

(Pointable (t u), Pointable u) => Pointable (UTU Co Co t u) Source # 
Instance details

Defined in Pandora.Pattern.Junction.Schemes.UTU

Methods

point :: a -> UTU Co Co t u a Source #

(Traversable (t u), Traversable u) => Traversable (UTU Co Co t u) Source # 
Instance details

Defined in Pandora.Pattern.Junction.Schemes.UTU

Methods

(->>) :: (Pointable u0, Applicative u0) => UTU Co Co t u a -> (a -> u0 b) -> (u0 :.: UTU Co Co t u) >< b Source #

traverse :: (Pointable u0, Applicative u0) => (a -> u0 b) -> UTU Co Co t u a -> (u0 :.: UTU Co Co t u) >< b Source #

sequence :: (Pointable u0, Applicative u0) => (UTU Co Co t u :.: u0) a -> (u0 :.: UTU Co Co t u) >< a Source #

(->>>) :: (Pointable u0, Applicative u0, Traversable v) => ((v :.: UTU Co Co t u) >< a) -> (a -> u0 b) -> (u0 :.: (v :.: UTU Co Co t u)) >< b Source #

(->>>>) :: (Pointable u0, Applicative u0, Traversable v, Traversable w) => ((w :.: (v :.: UTU Co Co t u)) >< a) -> (a -> u0 b) -> (u0 :.: (w :.: (v :.: UTU Co Co t u))) >< b Source #

(->>>>>) :: (Pointable u0, Applicative u0, Traversable v, Traversable w, Traversable j) => ((j :.: (w :.: (v :.: UTU Co Co t u))) >< a) -> (a -> u0 b) -> (u0 :.: (j :.: (w :.: (v :.: UTU Co Co t u)))) >< b Source #

Composition (UTU ct cu t u) Source # 
Instance details

Defined in Pandora.Pattern.Junction.Schemes.UTU

Associated Types

type Primary (UTU ct cu t u) a :: Type Source #

Methods

unwrap :: UTU ct cu t u a -> Primary (UTU ct cu t u) a Source #

(forall (u' :: k2 -> Type). Semigroup ((u' :.: t u') >< a)) => Semigroup (UTU Co Co t u a) Source # 
Instance details

Defined in Pandora.Pattern.Junction.Schemes.UTU

Methods

(+) :: UTU Co Co t u a -> UTU Co Co t u a -> UTU Co Co t u a Source #

(forall (u' :: k2 -> Type). Monoid ((u' :.: t u') >< a)) => Monoid (UTU Co Co t u a) Source # 
Instance details

Defined in Pandora.Pattern.Junction.Schemes.UTU

Methods

zero :: UTU Co Co t u a Source #

(forall (u' :: k2 -> Type). Setoid ((u' :.: t u') >< a)) => Setoid (UTU Co Co t u a) Source # 
Instance details

Defined in Pandora.Pattern.Junction.Schemes.UTU

Methods

(==) :: UTU Co Co t u a -> UTU Co Co t u a -> Boolean Source #

(/=) :: UTU Co Co t u a -> UTU Co Co t u a -> Boolean Source #

(forall (u' :: k2 -> Type). Chain ((u' :.: t u') >< a)) => Chain (UTU Co Co t u a) Source # 
Instance details

Defined in Pandora.Pattern.Junction.Schemes.UTU

Methods

(<=>) :: UTU Co Co t u a -> UTU Co Co t u a -> Ordering Source #

(<) :: UTU Co Co t u a -> UTU Co Co t u a -> Boolean Source #

(<=) :: UTU Co Co t u a -> UTU Co Co t u a -> Boolean Source #

(>) :: UTU Co Co t u a -> UTU Co Co t u a -> Boolean Source #

(>=) :: UTU Co Co t u a -> UTU Co Co t u a -> Boolean Source #

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

Defined in Pandora.Pattern.Junction.Schemes.UTU

type Primary (UTU ct cu t u) a = (u :.: t u) >< a