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

Pandora.Paradigm.Structure.Ability.Substructure

Documentation

class Substructure f t where Source #

Minimal complete definition

substructure

Associated Types

type Substructural (f :: k) (t :: * -> *) :: * -> * Source #

Instances

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Substructure ('Just :: a -> Maybe a) Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substructural 'Just Rose :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Substructure ('Just :: a -> Maybe a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substructural 'Just (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 Substructural '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 Substructural 'Left (Construction Wye) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

type Substructural 'Right (Product s) :: Type -> Type Source #

(Covariant t, Covariant (Substructural i t), Substructure i t, Substructure j (Substructural i t)) => Substructure (i |> j :: k2 -> Type) t Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

type Substructural (i |> j) t :: Type -> Type Source #

Methods

substructure :: (Tagged (i |> j) <:.> t) :~. Substructural (i |> j) t Source #

sub :: t :~. Substructural (i |> j) t Source #

data Segment a Source #

Constructors

Tail a 

Instances

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure

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

data ((i :: * -> k) |> (j :: * -> k')) a Source #

Instances

Instances details
(Covariant t, Covariant (Substructural i t), Substructure i t, Substructure j (Substructural i t)) => Substructure (i |> j :: k2 -> Type) t Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

Associated Types

type Substructural (i |> j) t :: Type -> Type Source #

Methods

substructure :: (Tagged (i |> j) <:.> t) :~. Substructural (i |> j) t Source #

sub :: t :~. Substructural (i |> j) t Source #

type Substructural (i |> j :: k2 -> Type) t Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Substructure

type Substructural (i |> j :: k2 -> Type) t = Substructural j (Substructural i t)

type Substructured i source target = (Substructure i source, Substructural i source ~ target) Source #