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

Pandora.Paradigm.Structure.Ability.Substructure

Documentation

class Substructure f t a where Source #

Associated Types

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

Methods

substructure :: Tagged f (t a) :-. Substructural f t a Source #

Instances

Instances details
Setoid a2 => Substructure ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) Stack a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural ('Delete 'First) Stack a2 Source #

Setoid a2 => Substructure ('Delete ('All :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural ('Delete 'All) (Construction Maybe) a2 Source #

Setoid a2 => Substructure ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural ('Delete 'First) (Construction Maybe) a2 Source #

Substructure ('Tail :: a1 -> Segment a1) Stack a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural 'Tail Stack a2 Source #

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

Defined in Pandora.Paradigm.Structure.Rose

Associated Types

type Substructural 'Just Rose a2 Source #

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

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural 'Right Binary a2 Source #

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

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural 'Left Binary a2 Source #

Substructure ('Right :: a1 -> Wye a1) Delta a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Substructural 'Right Delta a2 Source #

Substructure ('Left :: a1 -> Wye a1) Delta a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Substructural 'Left Delta a2 Source #

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

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural 'Tail (Construction Maybe) a2 Source #

Substructure ('Just :: a1 -> Maybe a1) (Construction Stack) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Rose

Associated Types

type Substructural 'Just (Construction Stack) a2 Source #

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

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural 'Right (Construction Wye) a2 Source #

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

Defined in Pandora.Paradigm.Structure.Binary

Associated Types

type Substructural 'Left (Construction Wye) a2 Source #

Substructure ('Tail :: a1 -> Segment a1) (Tap t) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Substructural 'Tail (Tap t) a2 Source #

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

Defined in Pandora.Paradigm.Structure

Associated Types

type Substructural 'Right (Product s) a2 Source #

Substructure ('Left :: a1 -> Wye a1) (Product s) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Substructural 'Left (Product s) a2 Source #

Substructure ('Right :: a1 -> Wye a1) (Delta <:.> t) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Substructural 'Right (Delta <:.> t) a2 Source #

Substructure ('Left :: a1 -> Wye a1) (Delta <:.> t) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Substructural 'Left (Delta <:.> t) a2 Source #

sub :: forall f t a. Substructure f t a => t a :-. Substructural f t a Source #

data Command a Source #

Constructors

Delete a 

Instances

Instances details
Setoid a2 => Substructure ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) Stack a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural ('Delete 'First) Stack a2 Source #

Setoid a2 => Substructure ('Delete ('All :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural ('Delete 'All) (Construction Maybe) a2 Source #

Setoid a2 => Substructure ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural ('Delete 'First) (Construction Maybe) a2 Source #

type Substructural ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) Stack a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Substructural ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) Stack a2 = a2 |-> Stack
type Substructural ('Delete ('All :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Substructural ('Delete ('All :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 = a2 |-> Stack
type Substructural ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Substructural ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 = a2 |-> Stack

data Segment a Source #

Constructors

All a 
First a 
Tail a 

Instances

Instances details
Setoid a2 => Substructure ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) Stack a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural ('Delete 'First) Stack a2 Source #

Setoid a2 => Substructure ('Delete ('All :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural ('Delete 'All) (Construction Maybe) a2 Source #

Setoid a2 => Substructure ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural ('Delete 'First) (Construction Maybe) a2 Source #

Substructure ('Tail :: a1 -> Segment a1) Stack a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural 'Tail Stack a2 Source #

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

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Substructural 'Tail (Construction Maybe) a2 Source #

Substructure ('Tail :: a1 -> Segment a1) (Tap t) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Substructural 'Tail (Tap t) a2 Source #

type Substructural ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) Stack a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Substructural ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) Stack a2 = a2 |-> Stack
type Substructural ('Delete ('All :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Substructural ('Delete ('All :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 = a2 |-> Stack
type Substructural ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Substructural ('Delete ('First :: a1 -> Segment a1) :: Command (a1 -> Segment a1)) (Construction Maybe) a2 = a2 |-> Stack
type Substructural ('Tail :: a1 -> Segment a1) Stack a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Substructural ('Tail :: a1 -> Segment a1) Stack a2 = Stack a2
type Substructural ('Tail :: a1 -> Segment a1) (Construction Maybe) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Substructural ('Tail :: a1 -> Segment a1) (Construction Maybe) a2 = Stack a2
type Substructural ('Tail :: a1 -> Segment a1) (Tap t) a2 Source # 
Instance details

Defined in Pandora.Paradigm.Structure

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