pandora-0.2.9: A box of patterns and paradigms

Safe HaskellSafe
LanguageHaskell2010

Pandora.Paradigm.Primary.Functor.Wye

Documentation

data Wye a Source #

Constructors

End 
Left a 
Right a 
Both a a 
Instances
Covariant Wye Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wye

Methods

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

comap :: (a -> b) -> Wye a -> Wye b Source #

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

($>) :: Wye a -> b -> Wye b Source #

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

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

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

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

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

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

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

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

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

Traversable Wye Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Wye

Methods

(->>) :: (Pointable u, Applicative u) => Wye a -> (a -> u b) -> (u :. Wye) := b Source #

traverse :: (Pointable u, Applicative u) => (a -> u b) -> Wye a -> (u :. Wye) := b Source #

sequence :: (Pointable u, Applicative u) => ((Wye :. u) := a) -> (u :. Wye) := a Source #

(->>>) :: (Pointable u, Applicative u, Traversable v) => ((v :. Wye) := a) -> (a -> u b) -> (u :. (v :. Wye)) := b Source #

(->>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w) => ((w :. (v :. Wye)) := a) -> (a -> u b) -> (u :. (w :. (v :. Wye))) := b Source #

(->>>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w, Traversable j) => ((j :. (w :. (v :. Wye))) := a) -> (a -> u b) -> (u :. (j :. (w :. (v :. Wye)))) := b Source #

Substructure (Left :: Type -> Wye Type) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural Left Binary a :: Type Source #

Substructure (Right :: Type -> Wye Type) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural Right Binary a :: Type Source #

(forall a. Chain a) => Focusable (Root :: Type -> Type) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Focusing Root Binary a :: Type Source #

Substructure (Left :: Type -> Wye Type) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural Left (Construction Wye) a :: Type Source #

Substructure (Right :: Type -> Wye Type) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural Right (Construction Wye) a :: Type Source #

Focusable (Root :: Type -> Type) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Focusing Root (Construction Wye) a :: Type Source #

Rotatable (Right (Zig :: a -> Splay a) :: Wye (a -> Splay a)) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Rotatable (Left (Zig :: a -> Splay a) :: Wye (a -> Splay a)) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Rotatable (Right (Zig (Zag :: a -> Splay a)) :: Wye (Splay (a -> Splay a))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Rotatable (Left (Zig (Zag :: a -> Splay a)) :: Wye (Splay (a -> Splay a))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Rotatable (Right (Zig (Zig :: a -> Splay a)) :: Wye (Splay (a -> Splay a))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Rotatable (Left (Zig (Zig :: a -> Splay a)) :: Wye (Splay (a -> Splay a))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Interpreted (Kan (Left :: Type -> Wye Type) t u b) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Kan

Associated Types

type Primary (Kan Left t u b) a :: Type Source #

Methods

run :: Kan Left t u b a -> Primary (Kan Left t u b) a Source #

Interpreted (Kan (Right :: Type -> Wye Type) t u b) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Kan

Associated Types

type Primary (Kan Right t u b) a :: Type Source #

Methods

run :: Kan Right t u b a -> Primary (Kan Right t u b) a Source #

Contravariant (Kan (Left :: Type -> Wye Type) t u b) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Kan

Methods

(>$<) :: (a -> b0) -> Kan Left t u b b0 -> Kan Left t u b a Source #

contramap :: (a -> b0) -> Kan Left t u b b0 -> Kan Left t u b a Source #

(>$) :: b0 -> Kan Left t u b b0 -> Kan Left t u b a Source #

($<) :: Kan Left t u b b0 -> b0 -> Kan Left t u b a Source #

full :: Kan Left t u b () -> Kan Left t u b a Source #

(>&<) :: Kan Left t u b b0 -> (a -> b0) -> Kan Left t u b a Source #

(>$$<) :: Contravariant u0 => (a -> b0) -> ((Kan Left t u b :. u0) := a) -> (Kan Left t u b :. u0) := b0 Source #

(>$$$<) :: (Contravariant u0, Contravariant v) => (a -> b0) -> ((Kan Left t u b :. (u0 :. v)) := b0) -> (Kan Left t u b :. (u0 :. v)) := a Source #

(>$$$$<) :: (Contravariant u0, Contravariant v, Contravariant w) => (a -> b0) -> ((Kan Left t u b :. (u0 :. (v :. w))) := a) -> (Kan Left t u b :. (u0 :. (v :. w))) := b0 Source #

(>&&<) :: Contravariant u0 => ((Kan Left t u b :. u0) := a) -> (a -> b0) -> (Kan Left t u b :. u0) := b0 Source #

(>&&&<) :: (Contravariant u0, Contravariant v) => ((Kan Left t u b :. (u0 :. v)) := b0) -> (a -> b0) -> (Kan Left t u b :. (u0 :. v)) := a Source #

(>&&&&<) :: (Contravariant u0, Contravariant v, Contravariant w) => ((Kan Left t u b :. (u0 :. (v :. w))) := a) -> (a -> b0) -> (Kan Left t u b :. (u0 :. (v :. w))) := b0 Source #

Covariant (Kan (Right :: Type -> Wye Type) t u b) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Kan

Methods

(<$>) :: (a -> b0) -> Kan Right t u b a -> Kan Right t u b b0 Source #

comap :: (a -> b0) -> Kan Right t u b a -> Kan Right t u b b0 Source #

(<$) :: a -> Kan Right t u b b0 -> Kan Right t u b a Source #

($>) :: Kan Right t u b a -> b0 -> Kan Right t u b b0 Source #

void :: Kan Right t u b a -> Kan Right t u b () Source #

loeb :: Kan Right t u b (a <-| Kan Right t u b) -> Kan Right t u b a Source #

(<&>) :: Kan Right t u b a -> (a -> b0) -> Kan Right t u b b0 Source #

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

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

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

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

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

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

type Nonempty Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

data Kan (Left :: Type -> Wye Type) t u b a Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Kan

data Kan (Left :: Type -> Wye Type) t u b a = Lan ((t b -> a) -> u b)
data Kan (Right :: Type -> Wye Type) t u b a Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Kan

data Kan (Right :: Type -> Wye Type) t u b a = Ran ((a -> t b) -> u b)
type Substructural (Left :: Type -> Wye Type) Binary a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Substructural (Left :: Type -> Wye Type) Binary a = Binary a
type Substructural (Right :: Type -> Wye Type) Binary a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Substructural (Right :: Type -> Wye Type) Binary a = Binary a
type Focusing (Root :: Type -> Type) Binary a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Focusing (Root :: Type -> Type) Binary a = Maybe a
type Substructural (Left :: Type -> Wye Type) (Construction Wye) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Substructural (Left :: Type -> Wye Type) (Construction Wye) a = (Maybe :. Construction Wye) := a
type Substructural (Right :: Type -> Wye Type) (Construction Wye) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Substructural (Right :: Type -> Wye Type) (Construction Wye) a = (Maybe :. Construction Wye) := a
type Focusing (Root :: Type -> Type) (Construction Wye) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Focusing (Root :: Type -> Type) (Construction Wye) a = a
type Primary (Kan (Left :: Type -> Wye Type) t u b) a Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Kan

type Primary (Kan (Left :: Type -> Wye Type) t u b) a = (t b -> a) -> u b
type Primary (Kan (Right :: Type -> Wye Type) t u b) a Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Kan

type Primary (Kan (Right :: Type -> Wye Type) t u b) a = (a -> t b) -> u b

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