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

Pandora.Paradigm.Structure.Ability.Substructure

Documentation

data Segment a Source #

Constructors

Root a 
Tail a 

Instances

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substance 'Tail 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 ('Root :: a -> Segment a) (Tap ((t <:.:> t) > (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

Associated Types

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

Substructure ('Root :: a -> Segment a) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Substance 'Root (Construction (Maybe <:*:> Maybe)) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Substructure ('Tail :: a -> Segment a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substance 'Tail (Construction Maybe) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance 'Tail (Construction List) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

type Substance ('Tail :: 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 ('Root :: a -> Segment a) (Tap ((t <:.:> t) > (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

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

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.List

type Substance ('Tail :: a -> Segment a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.Rose

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

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Tail :: a -> Segment a) (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Substance ('Tail :: a -> Segment a) (Tap t) = t

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, Semimonoidal (-->) (:*:) (:*:) t) => Substructure ('All ('Right :: a -> Wye a) :: Occurrence (a -> Wye a)) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Zipper

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 -> Wye a) :: Occurrence (a -> Wye a)) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Zipper

Associated Types

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

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

Defined in Pandora.Paradigm.Primary

Associated Types

type Substance 'Right Wye :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Primary

Associated Types

type Substance 'Left Wye :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substance 'Tail 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 ('Right :: a -> Wye a) (Tap ((t <:.:> t) > (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Associated Types

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

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Left :: a -> Wye a) (Tap ((t <:.:> t) > (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Associated Types

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

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

Defined in Pandora.Paradigm.Primary.Transformer.Tap

Associated Types

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

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Right :: a -> Wye a) (Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Zipper

Associated Types

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

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Left :: a -> Wye a) (Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Zipper

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Ability.Zipper

Associated Types

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

Substructure ('Root :: a -> Segment a) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Substance 'Root (Construction (Maybe <:*:> Maybe)) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Substance 'Right (Construction (Maybe <:*:> Maybe)) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Substance 'Left (Construction (Maybe <:*:> Maybe)) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Substructure ('Tail :: a -> Segment a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substance 'Tail (Construction Maybe) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance 'Tail (Construction List) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance 'Root (Construction List) :: 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 ('Tail :: a -> Segment a) (Tap t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Substance 'Tail (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 -> Wye 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 -> Wye 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 ('Down :: a -> Vertical a) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Zipper

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.Ability.Zipper

Associated Types

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