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

Pandora.Paradigm.Structure.Ability.Substructure

Documentation

type Substructured segment source target = (Substructure segment source, Substance segment source ~ target) Source #

class Substructure segment (structure :: * -> *) where Source #

Minimal complete definition

substructure

Associated Types

type Substance segment structure :: * -> * Source #

Methods

substructure :: (Tagged segment <:.> structure) @>>> Substance segment structure Source #

sub :: Covariant (->) (->) structure => structure @>>> Substance segment structure Source #

Instances

Instances details
(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) structure, Substructure segment structure) => Substructure (segment :: k) (Turnover structure) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Turnover

Associated Types

type Substance segment (Turnover structure) :: Type -> Type Source #

Methods

substructure :: (Tagged segment <:.> Turnover structure) @>>> Substance segment (Turnover structure) Source #

sub :: Turnover structure @>>> Substance segment (Turnover structure) Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Substructure i t) => Substructure (i ('Branch :: a -> Segment a) :: k) (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

type Substance (i 'Branch) (Construction t) :: Type -> Type Source #

Substructure ('Right ('Branch :: a -> Segment a) :: Horizontal (a -> Segment a)) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Substance ('Right 'Branch) Binary :: Type -> Type Source #

Substructure ('Left ('Branch :: a -> Segment a) :: Horizontal (a -> Segment a)) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Substance ('Left 'Branch) Binary :: Type -> Type Source #

Substructure ('Right ('Forest :: a -> Segment a) :: Horizontal (a -> Segment a)) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Right 'Forest) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) :: Type -> Type Source #

Substructure ('Left ('Forest :: a -> Segment a) :: Horizontal (a -> Segment a)) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Left 'Forest) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) :: Type -> Type Source #

Substructure ('Down ('Forest :: a -> Segment a) :: Vertical (a -> Segment a)) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Down 'Forest) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) :: Type -> Type Source #

Substructure ('Up ('Forest :: a -> Segment a) :: Vertical (a -> Segment a)) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Up 'Forest) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) :: Type -> Type Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal (-->) (:*:) (:*:) t) => Substructure ('All ('Right :: a -> Horizontal a) :: Occurrence (a -> Horizontal a)) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

type Substance ('All 'Right) (Tape t <::> Tape t) :: Type -> Type Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal (-->) (:*:) (:*:) t) => Substructure ('All ('Left :: a -> Horizontal a) :: Occurrence (a -> Horizontal a)) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

type Substance ('All 'Left) (Tape t <::> Tape t) :: Type -> Type Source #

Substructure ('Rest :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substance 'Rest List :: Type -> Type Source #

Substructure ('Root :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substance 'Root List :: 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 #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Rest :: a -> Segment a) (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

type Substance 'Rest (Construction t) :: Type -> Type Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Root :: a -> Segment a) (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

type Substance 'Root (Construction t) :: 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 #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Rest :: a -> Segment a) (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Substance 'Rest (Tap t) :: 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) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Substructure ('Right :: a -> Horizontal a) (t <:*:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

type Substance 'Right (t <:*:> u) :: Type -> Type Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) u) => Substructure ('Left :: a -> Horizontal a) (t <:*:> u) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

type Substance 'Left (t <:*:> u) :: Type -> Type Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Rest :: a -> Segment a) (Exactly <:*:> t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

type Substance 'Rest (Exactly <:*:> t) :: Type -> Type Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Root :: a -> Segment a) (Exactly <:*:> t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

type Substance 'Root (Exactly <:*:> t) :: Type -> Type Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Down :: a -> Vertical a) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

type Substance 'Down (Tape t <::> Tape t) :: Type -> Type Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Up :: a -> Vertical a) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

type Substance 'Up (Tape t <::> Tape t) :: Type -> Type Source #

tagstruct :: Covariant (->) (->) structure => (Tagged segment <:.> structure) @>>> structure Source #

data Segment a Source #

Constructors

Root a 
Rest a 
Branch a 
Ancestors a 
Forest a 

Instances

Instances details
Substructure ('Right ('Branch :: a -> Segment a) :: Horizontal (a -> Segment a)) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Substance ('Right 'Branch) Binary :: Type -> Type Source #

Substructure ('Left ('Branch :: a -> Segment a) :: Horizontal (a -> Segment a)) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Substance ('Left 'Branch) Binary :: Type -> Type Source #

Substructure ('Right ('Forest :: a -> Segment a) :: Horizontal (a -> Segment a)) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Right 'Forest) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) :: Type -> Type Source #

Substructure ('Left ('Forest :: a -> Segment a) :: Horizontal (a -> Segment a)) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Left 'Forest) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) :: Type -> Type Source #

Substructure ('Down ('Forest :: a -> Segment a) :: Vertical (a -> Segment a)) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Down 'Forest) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) :: Type -> Type Source #

Substructure ('Up ('Forest :: a -> Segment a) :: Vertical (a -> Segment a)) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Up 'Forest) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) :: Type -> Type Source #

Substructure ('Rest :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substance 'Rest List :: Type -> Type Source #

Substructure ('Root :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substance 'Root List :: Type -> Type Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Rest :: a -> Segment a) (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

type Substance 'Rest (Construction t) :: Type -> Type Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Root :: a -> Segment a) (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

type Substance 'Root (Construction t) :: Type -> Type Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Rest :: a -> Segment a) (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Substance 'Rest (Tap t) :: Type -> Type Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Rest :: a -> Segment a) (Exactly <:*:> t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

type Substance 'Rest (Exactly <:*:> t) :: Type -> Type Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Root :: a -> Segment a) (Exactly <:*:> t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

type Substance 'Root (Exactly <:*:> t) :: Type -> Type Source #

type Substance ('Right ('Branch :: a -> Segment a) :: Horizontal (a -> Segment a)) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substance ('Right ('Branch :: a -> Segment a) :: Horizontal (a -> Segment a)) Binary = Binary
type Substance ('Left ('Branch :: a -> Segment a) :: Horizontal (a -> Segment a)) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substance ('Left ('Branch :: a -> Segment a) :: Horizontal (a -> Segment a)) Binary = Binary
type Substance ('Right ('Forest :: a -> Segment a) :: Horizontal (a -> Segment a)) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Left ('Forest :: a -> Segment a) :: Horizontal (a -> Segment a)) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Down ('Forest :: a -> Segment a) :: Vertical (a -> Segment a)) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Up ('Forest :: a -> Segment a) :: Vertical (a -> Segment a)) (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Rest :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substance ('Rest :: a -> Segment a) List = List
type Substance ('Root :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substance ('Root :: a -> Segment a) List = Maybe
type Substance ('Rest :: a -> Segment a) (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

type Substance ('Rest :: a -> Segment a) (Construction t) = t <::> Construction t
type Substance ('Root :: a -> Segment a) (Construction t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

type Substance ('Root :: a -> Segment a) (Construction t) = Exactly
type Substance ('Rest :: a -> Segment a) (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Substance ('Rest :: a -> Segment a) (Tap t) = t
type Substance ('Rest :: a -> Segment a) (Exactly <:*:> t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

type Substance ('Rest :: a -> Segment a) (Exactly <:*:> t) = t
type Substance ('Root :: a -> Segment a) (Exactly <:*:> t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

type Substance ('Root :: a -> Segment a) (Exactly <:*:> t) = Exactly