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

Pandora.Paradigm.Structure.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
Morphable ('Down ('Right :: a -> Wye a) :: Vertical (a -> Wye a)) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Morphable ('Down ('Left :: a -> Wye a) :: Vertical (a -> Wye a)) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Morphable ('Up :: a -> Vertical a) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Morphing ('Down ('Right :: a -> Wye a) :: Vertical (a -> Wye a)) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Morphing ('Down ('Left :: a -> Wye a) :: Vertical (a -> Wye a)) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Morphing ('Up :: a -> Vertical a) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

data Vertical a Source #

Constructors

Up a 
Down a 

Instances

Instances details
Morphable ('Down ('Right :: a -> Wye a) :: Vertical (a -> Wye a)) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Morphable ('Down ('Left :: a -> Wye a) :: Vertical (a -> Wye a)) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Morphable ('Up :: a -> Vertical a) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Morphing ('Down ('Right :: a -> Wye a) :: Vertical (a -> Wye a)) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Morphing ('Down ('Left :: a -> Wye a) :: Vertical (a -> Wye a)) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Morphing ('Up :: a -> Vertical a) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Orphan instances

(forall a. Chain a) => Insertable Binary Source # 
Instance details

Methods

insert :: a -> Binary a -> Binary a Source #

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 #

(forall a. Chain a) => Insertable (Construction Wye) Source # 
Instance details

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 #

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 #

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 #