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

Pandora.Paradigm.Structure.Some.Binary

Documentation

binary :: forall t a. (Traversable t, Chain a) => t a -> Binary a Source #

data Biforked a Source #

Constructors

Top 
Leftward a 
Rightward a 

Instances

Instances details
Covariant Biforked Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Methods

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

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

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

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

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

loeb :: Biforked (a <:= Biforked) -> Biforked a Source #

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

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

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

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

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

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

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

Morphable ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate 'Up) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

Morphable ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate ('Down 'Right)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

Morphable ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate ('Down 'Left)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

type Morphing ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

data Vertical a Source #

Constructors

Up a 
Down a 

Instances

Instances details
Morphable ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate 'Up) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

Morphable ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate ('Down 'Right)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

Morphable ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate ('Down 'Left)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

type Morphing ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Orphan instances

Measurable 'Heighth Binary Source # 
Instance details

Associated Types

type Measural 'Heighth Binary a Source #

Measurable 'Heighth (Construction Wye) Source # 
Instance details

Associated Types

type Measural 'Heighth (Construction Wye) a Source #

Nullable Binary Source # 
Instance details

Methods

null :: forall (a :: k). (Predicate :. Binary) := a Source #

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

Associated Types

type Focusing 'Root Binary a Source #

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

Associated Types

type Focusing 'Root (Construction Wye) a Source #

Morphable ('Into Binary) (Construction Wye) Source # 
Instance details

Associated Types

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

Morphable ('Insert :: a -> Morph a) Binary Source # 
Instance details

Associated Types

type Morphing 'Insert Binary :: Type -> Type Source #

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

Associated Types

type Substructural 'Right Binary :: Type -> Type Source #

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

Associated Types

type Substructural 'Left Binary :: Type -> Type Source #

Morphable ('Insert :: a -> Morph a) (Construction Wye) Source # 
Instance details

Associated Types

type Morphing 'Insert (Construction Wye) :: Type -> Type Source #

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

Associated Types

type Substructural 'Right (Construction Wye) :: Type -> Type Source #

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

Associated Types

type Substructural 'Left (Construction Wye) :: Type -> Type Source #