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

Pandora.Paradigm.Structure.Binary

Documentation

data Biforked a Source #

Constructors

Top 
Leftward a 
Rightward a 

Instances

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

Defined in Pandora.Paradigm.Structure.Binary

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

Defined in Pandora.Paradigm.Structure.Binary

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

Defined in Pandora.Paradigm.Structure.Binary

type Rotational ('Down ('Right :: a1 -> Wye a1) :: Vertical (a1 -> Wye a1)) (Construction Wye <:*:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Rotational ('Down ('Left :: a1 -> Wye a1) :: Vertical (a1 -> Wye a1)) (Construction Wye <:*:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Rotational ('Up :: a1 -> Vertical a1) (Construction Wye <:*:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

data Vertical a Source #

Constructors

Up a 
Down a 

Instances

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

Defined in Pandora.Paradigm.Structure.Binary

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

Defined in Pandora.Paradigm.Structure.Binary

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

Defined in Pandora.Paradigm.Structure.Binary

type Rotational ('Down ('Right :: a1 -> Wye a1) :: Vertical (a1 -> Wye a1)) (Construction Wye <:*:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Rotational ('Down ('Left :: a1 -> Wye a1) :: Vertical (a1 -> Wye a1)) (Construction Wye <:*:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

type Rotational ('Up :: a1 -> Vertical a1) (Construction Wye <:*:> ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) a2 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 #

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

Nullable Binary Source # 
Instance details

Methods

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

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

Associated Types

type Substructural 'Left Binary a Source #

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

Associated Types

type Substructural 'Right Binary a Source #

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

Associated Types

type Focusing 'Root Binary a Source #

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

Associated Types

type Substructural 'Left (Construction Wye) a Source #

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

Associated Types

type Substructural 'Right (Construction Wye) a Source #

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

Associated Types

type Focusing 'Root (Construction Wye) a Source #