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

Pandora.Paradigm.Structure.Ability.Morphable

Documentation

class Morphable f t where Source #

Associated Types

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

Methods

morphing :: (Tagged f <:.> t) ~> Morphing f t Source #

Instances

Instances details
Morphable o (Construction Wye) => Morphable (o :: k) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing o Binary :: Type -> Type Source #

Morphable ('Right ('Zig :: a -> Splay a) :: Wye (a -> Splay a)) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

Associated Types

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

Morphable ('Left ('Zig :: a -> Splay a) :: Wye (a -> Splay a)) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

Associated Types

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

Morphable ('Right ('Zig ('Zag :: a -> Splay a)) :: Wye (Splay (a -> Splay a))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

Associated Types

type Morphing ('Right ('Zig 'Zag)) (Construction Wye) :: Type -> Type Source #

Morphable ('Left ('Zig ('Zag :: a -> Splay a)) :: Wye (Splay (a -> Splay a))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

Associated Types

type Morphing ('Left ('Zig 'Zag)) (Construction Wye) :: Type -> Type Source #

Morphable ('Right ('Zig ('Zig :: a -> Splay a)) :: Wye (Splay (a -> Splay a))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

Associated Types

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

Morphable ('Left ('Zig ('Zig :: a -> Splay a)) :: Wye (Splay (a -> Splay a))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Splay

Associated Types

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

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

Associated Types

type Morphing ('Rotate 'Right) (Tap ((:*:) <:.:> Stream)) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

Associated Types

type Morphing ('Rotate 'Left) (Tap ((:*:) <:.:> Stream)) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Construction Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Morphing ('Rotate 'Right) (Tap ((:*:) <:.:> Construction Maybe)) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Construction Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Morphing ('Rotate 'Left) (Tap ((:*:) <:.:> Construction Maybe)) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stack)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Morphing ('Rotate 'Right) (Tap ((:*:) <:.:> Stack)) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stack)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Morphing ('Rotate 'Left) (Tap ((:*:) <:.:> Stack)) :: Type -> Type Source #

Morphable ('Down ('Right :: a -> Wye a) :: Vertical (a -> Wye a)) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Morphable ('Down ('Left :: a -> Wye a) :: Vertical (a -> Wye a)) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

Morphable Stack (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Morphing Stack (Construction Maybe) :: Type -> Type Source #

Morphable ('Postorder :: a -> Walk a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing 'Postorder (Construction Wye) :: Type -> Type Source #

Morphable ('Inorder :: a -> Walk a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing 'Inorder (Construction Wye) :: Type -> Type Source #

Morphable ('Preorder :: a -> Walk a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing 'Preorder (Construction Wye) :: Type -> Type Source #

Morphable ('Up :: a -> Vertical a) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_ Covariant (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Binary

morph :: forall f t. Morphable f t => t ~> Morphing f t Source #

data Walk a Source #

Constructors

Preorder a 
Inorder a 
Postorder a 
Levelorder a 

Instances

Instances details
Morphable ('Postorder :: a -> Walk a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing 'Postorder (Construction Wye) :: Type -> Type Source #

Morphable ('Inorder :: a -> Walk a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing 'Inorder (Construction Wye) :: Type -> Type Source #

Morphable ('Preorder :: a -> Walk a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing 'Preorder (Construction Wye) :: Type -> Type Source #

type Morphing ('Postorder :: a -> Walk a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Inorder :: a -> Walk a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Preorder :: a -> Walk a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

data Morph a Source #

Constructors

Rotate a 

Instances

Instances details
Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

Associated Types

type Morphing ('Rotate 'Right) (Tap ((:*:) <:.:> Stream)) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

Associated Types

type Morphing ('Rotate 'Left) (Tap ((:*:) <:.:> Stream)) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Construction Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Morphing ('Rotate 'Right) (Tap ((:*:) <:.:> Construction Maybe)) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Construction Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Morphing ('Rotate 'Left) (Tap ((:*:) <:.:> Construction Maybe)) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stack)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Morphing ('Rotate 'Right) (Tap ((:*:) <:.:> Stack)) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stack)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

Associated Types

type Morphing ('Rotate 'Left) (Tap ((:*:) <:.:> Stack)) :: Type -> Type Source #

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stream)) = Tap ((:*:) <:.:> Stream)
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stream)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stream

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stream)) = Tap ((:*:) <:.:> Stream)
type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Construction Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Construction Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stack)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stack)) = Maybe <:.> Zipper Stack
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stack)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Stack

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stack)) = Maybe <:.> Zipper Stack