pandora-0.4.7: 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 Available 'Tail List :: Type -> Type Source #

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 Available 'Root List :: Type -> Type Source #

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 Available 'Root (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source #

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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 Available 'Tail (Construction Maybe) :: Type -> Type Source #

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 Available 'Tail (Construction List) :: Type -> Type Source #

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 Available 'Root (Construction List) :: Type -> Type Source #

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Available 'Root (Construction Wye) :: Type -> Type Source #

type Substance 'Root (Construction Wye) :: 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 Available 'Tail (Tap t) :: Type -> Type Source #

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

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

Defined in Pandora.Paradigm.Structure.Some.List

type Available ('Tail :: a -> Segment a) List = Identity
type Available ('Root :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Available ('Root :: a -> Segment a) List = Maybe
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 = Identity
type Available ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Tap

type Available ('Root :: a -> Segment a) (Tap ((t <:.:> t) := (:*:))) = Identity
type Available ('Root :: a -> Segment a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.Rose

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

Defined in Pandora.Paradigm.Structure.Some.Rose

type Available ('Root :: a -> Segment a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure

type Available ('Tail :: a -> Segment a) (Tap t) = Identity
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) := (:*:))) = Identity
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 ('Root :: a -> Segment a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

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 available target = (Substructure segment source, Substance segment source ~ target, Available segment source ~ available) Source #

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

Minimal complete definition

substructure

Associated Types

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

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

Methods

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

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

Instances

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Available 'Tail List :: Type -> Type Source #

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 Available 'Root List :: Type -> Type Source #

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

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

Defined in Pandora.Paradigm.Primary

Associated Types

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

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

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

Defined in Pandora.Paradigm.Primary

Associated Types

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

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 Available 'Right Binary :: Type -> Type Source #

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 Available 'Left Binary :: Type -> Type Source #

type Substance 'Left Binary :: 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 Available 'Right (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source #

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 Available 'Left (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source #

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 Available 'Root (Tap ((t <:.:> t) := (:*:))) :: Type -> Type Source #

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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 Available 'Tail (Construction Maybe) :: Type -> Type Source #

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 Available 'Tail (Construction List) :: Type -> Type Source #

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 Available 'Root (Construction List) :: Type -> Type Source #

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Available 'Root (Construction Wye) :: Type -> Type Source #

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

type Available 'Right ((:*:) s) :: Type -> Type Source #

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 Available 'Tail (Tap t) :: Type -> Type Source #

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 Available 'Left (Flip (:*:) a2) :: Type -> Type Source #

type Substance 'Left (Flip (:*:) a2) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure

Associated Types

type Available 'Right ((t <:.:> t) := (:*:)) :: Type -> Type Source #

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

type Available 'Left ((t <:.:> t) := (:*:)) :: Type -> Type Source #

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