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

Pandora.Paradigm.Primary.Functor.Wye

Documentation

data Wye a Source #

Constructors

End 
Left_ a 
Right_ a 
Both a a 

Instances

Instances details
Monotonic a (Wye a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wye

Methods

reduce :: (a -> r -> r) -> r -> Wye a -> r Source #

resolve :: (a -> r) -> r -> Wye a -> r Source #

Semigroup a => Semigroup (Wye a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wye

Methods

(+) :: Wye a -> Wye a -> Wye a Source #

Semigroup a => Monoid (Wye a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wye

Methods

zero :: Wye a Source #

Morphable ('Into ('Left_ Maybe)) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing ('Into ('Left_ Maybe)) Wye :: Type -> Type Source #

Morphable ('Into ('Right_ Maybe)) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing ('Into ('Right_ Maybe)) Wye :: Type -> Type Source #

Morphable ('Into ('Preorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing ('Into ('Preorder (Construction Maybe))) (Construction Wye) :: Type -> Type Source #

Morphable ('Into ('Inorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing ('Into ('Inorder (Construction Maybe))) (Construction Wye) :: Type -> Type Source #

Morphable ('Into ('Postorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing ('Into ('Postorder (Construction Maybe))) (Construction Wye) :: Type -> Type Source #

Morphable ('Into Wye) (Maybe <:*:> Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing ('Into Wye) (Maybe <:*:> Maybe) :: Type -> Type Source #

Substructure ('Right_ :: a -> Wye a) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Substance 'Right_ Wye :: Type -> Type Source #

Substructure ('Left_ :: a -> Wye a) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Substance 'Left_ Wye :: Type -> Type Source #

Substructure ('Right_ :: a -> Wye a) ((:*:) s) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Substance 'Right_ ((:*:) s) :: Type -> Type Source #

Substructure ('Left_ :: a1 -> Wye a1) (Flip (:*:) a2) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Substance 'Left_ (Flip (:*:) a2) :: Type -> Type Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wye

Methods

(<-|-) :: (a -> b) -> Wye a -> Wye b Source #

(<-|--) :: (a -> b) -> Wye a -> Wye b Source #

(<-|---) :: (a -> b) -> Wye a -> Wye b Source #

(<-|----) :: (a -> b) -> Wye a -> Wye b Source #

(<-|-----) :: (a -> b) -> Wye a -> Wye b Source #

(<-|------) :: (a -> b) -> Wye a -> Wye b Source #

(<-|-------) :: (a -> b) -> Wye a -> Wye b Source #

(<-|--------) :: (a -> b) -> Wye a -> Wye b Source #

(<-|-|-) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) Wye) => (a -> b) -> Wye (u a) -> Wye (u b) Source #

(<-|-|--) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) Wye) => (a -> b) -> Wye (u a) -> Wye (u b) Source #

(<-|-|---) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) Wye) => (a -> b) -> Wye (u a) -> Wye (u b) Source #

(<-|-|----) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) Wye) => (a -> b) -> Wye (u a) -> Wye (u b) Source #

(<-|-|-----) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) Wye) => (a -> b) -> Wye (u a) -> Wye (u b) Source #

(<-|-|------) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) Wye) => (a -> b) -> Wye (u a) -> Wye (u b) Source #

(<-|-|-------) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) Wye) => (a -> b) -> Wye (u a) -> Wye (u b) Source #

(<-|-|-|-) :: (Covariant (->) (Betwixt (->) (Betwixt (->) (->))) v, Covariant (Betwixt (->) (Betwixt (->) (->))) (Betwixt (Betwixt (->) (->)) (->)) u, Covariant (Betwixt (Betwixt (->) (->)) (->)) (->) Wye) => (a -> b) -> Wye (u (v a)) -> Wye (u (v b)) Source #

type Morphing ('Into ('Left_ Maybe)) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into ('Right_ Maybe)) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into ('Preorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into ('Inorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into ('Postorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into Wye) (Maybe <:*:> Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Substance ('Right_ :: a -> Wye a) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Substance ('Right_ :: a -> Wye a) Wye = Maybe
type Substance ('Left_ :: a -> Wye a) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Substance ('Left_ :: a -> Wye a) Wye = Maybe
type Substance ('Right_ :: a -> Wye a) ((:*:) s) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Substance ('Right_ :: a -> Wye a) ((:*:) s) = Exactly
type Substance ('Left_ :: a1 -> Wye a1) (Flip (:*:) a2) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Substance ('Left_ :: a1 -> Wye a1) (Flip (:*:) a2) = Exactly

wye :: r -> (a -> r) -> (a -> r) -> (a -> a -> r) -> Wye a -> r Source #