pandora-0.3.7: 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 ('Into (Conclusion e) :: Morph (Type -> Type)) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into (Conclusion e)) Maybe :: Type -> Type Source #

Morphable ('Into (o ds)) (Construction Wye) => Morphable ('Into (o ds) :: Morph a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing ('Into (o ds)) Binary :: Type -> Type Source #

Methods

morphing :: (Tagged ('Into (o ds)) <:.> Binary) ~> Morphing ('Into (o ds)) Binary Source #

Morphable ('Into ('Left Maybe)) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into ('Left Maybe)) Wye :: Type -> Type Source #

Morphable ('Into ('Right Maybe)) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into ('Right Maybe)) Wye :: Type -> Type Source #

Morphable ('Into Maybe) (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into Maybe) (Conclusion e) :: Type -> Type Source #

Morphable ('Into Stack) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stack

Associated Types

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

Morphable ('Into Binary) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Into Binary) (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.Some.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.Some.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.Some.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.Some.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.Some.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.Some.Stack

Associated Types

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

Morphable ('Into ('There Maybe :: Wedge e1 (Type -> Type)) :: Morph (Wedge e1 (Type -> Type))) (Wedge e2) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into ('There Maybe)) (Wedge e2) :: Type -> Type Source #

Morphable ('Into ('This Maybe :: These e1 (Type -> Type)) :: Morph (These e1 (Type -> Type))) (These e2) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into ('This Maybe)) (These e2) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable ('Into ('Preorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into ('Inorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into ('Postorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into ('Here Maybe :: Wedge (Type -> Type) a1) :: Morph (Wedge (Type -> Type) a1)) (Flip Wedge a2) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into ('Here Maybe)) (Flip Wedge a2) :: Type -> Type Source #

Morphable ('Into ('That Maybe :: These (Type -> Type) a1) :: Morph (These (Type -> Type) a1)) (Flip These a2) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into ('That Maybe)) (Flip These a2) :: Type -> Type Source #

Morphable ('Into Wye) ((:*:) <:.:> Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into Wye) ((:*:) <:.:> Maybe) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.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 ('Into ('Preorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into ('Inorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into ('Postorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

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

type Morphing ('Into ('Preorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into ('Inorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into ('Postorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

data Morph a Source #

Constructors

Rotate a 
Into a 

Instances

Instances details
Morphable ('Into (Conclusion e) :: Morph (Type -> Type)) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into (Conclusion e)) Maybe :: Type -> Type Source #

Morphable ('Into (o ds)) (Construction Wye) => Morphable ('Into (o ds) :: Morph a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing ('Into (o ds)) Binary :: Type -> Type Source #

Methods

morphing :: (Tagged ('Into (o ds)) <:.> Binary) ~> Morphing ('Into (o ds)) Binary Source #

Morphable ('Into ('Left Maybe)) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into ('Left Maybe)) Wye :: Type -> Type Source #

Morphable ('Into ('Right Maybe)) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into ('Right Maybe)) Wye :: Type -> Type Source #

Morphable ('Into Maybe) (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into Maybe) (Conclusion e) :: Type -> Type Source #

Morphable ('Into Stack) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stack

Associated Types

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

Morphable ('Into Binary) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Into Binary) (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.Some.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.Some.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.Some.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.Some.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.Some.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.Some.Stack

Associated Types

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

Morphable ('Into ('There Maybe :: Wedge e1 (Type -> Type)) :: Morph (Wedge e1 (Type -> Type))) (Wedge e2) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into ('There Maybe)) (Wedge e2) :: Type -> Type Source #

Morphable ('Into ('This Maybe :: These e1 (Type -> Type)) :: Morph (These e1 (Type -> Type))) (These e2) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into ('This Maybe)) (These e2) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable ('Into ('Preorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into ('Inorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into ('Postorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into ('Here Maybe :: Wedge (Type -> Type) a1) :: Morph (Wedge (Type -> Type) a1)) (Flip Wedge a2) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into ('Here Maybe)) (Flip Wedge a2) :: Type -> Type Source #

Morphable ('Into ('That Maybe :: These (Type -> Type) a1) :: Morph (These (Type -> Type) a1)) (Flip These a2) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into ('That Maybe)) (Flip These a2) :: Type -> Type Source #

Morphable ('Into Wye) ((:*:) <:.:> Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into Wye) ((:*:) <:.:> Maybe) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Into (Conclusion e) :: Morph (Type -> Type)) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary

type Morphing ('Into (Conclusion e) :: Morph (Type -> Type)) Maybe = ((->) e :: Type -> Type) <:.> Conclusion e
type Morphing ('Into (o ds) :: Morph a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into (o ds) :: Morph a) Binary = Maybe <:.> Morphing ('Into (o ds)) (Construction Wye)
type Morphing ('Into ('Left Maybe)) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Primary

type Morphing ('Into ('Right Maybe)) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Primary

type Morphing ('Into Maybe) (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

type Morphing ('Into Stack) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stack

type Morphing ('Into Binary) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.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.Some.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.Some.Stack

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

Defined in Pandora.Paradigm.Structure.Some.Stack

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

Defined in Pandora.Paradigm.Structure.Some.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.Some.Stack

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((:*:) <:.:> Stack)) = Maybe <:.> Zipper Stack
type Morphing ('Into ('There Maybe :: Wedge e1 (Type -> Type)) :: Morph (Wedge e1 (Type -> Type))) (Wedge e2) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

type Morphing ('Into ('There Maybe :: Wedge e1 (Type -> Type)) :: Morph (Wedge e1 (Type -> Type))) (Wedge e2) = Maybe
type Morphing ('Into ('This Maybe :: These e1 (Type -> Type)) :: Morph (These e1 (Type -> Type))) (These e2) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

type Morphing ('Into ('This Maybe :: These e1 (Type -> Type)) :: Morph (These e1 (Type -> Type))) (These e2) = Maybe
type Morphing ('Rotate ('Right ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Right ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) (Construction Wye) = Binary
type Morphing ('Rotate ('Left ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Left ('Zig :: a -> Splay a)) :: Morph (Wye (a -> Splay a))) (Construction Wye) = Binary
type Morphing ('Rotate ('Right ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Right ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) = Binary
type Morphing ('Rotate ('Left ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Left ('Zig ('Zag :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) = Binary
type Morphing ('Rotate ('Right ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Right ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) = Binary
type Morphing ('Rotate ('Left ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing ('Rotate ('Left ('Zig ('Zig :: a -> Splay a))) :: Morph (Wye (Splay (a -> Splay a)))) (Construction Wye) = Binary
type Morphing ('Into ('Preorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into ('Inorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into ('Postorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into ('Here Maybe :: Wedge (Type -> Type) a1) :: Morph (Wedge (Type -> Type) a1)) (Flip Wedge a2) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

type Morphing ('Into ('Here Maybe :: Wedge (Type -> Type) a1) :: Morph (Wedge (Type -> Type) a1)) (Flip Wedge a2) = Maybe
type Morphing ('Into ('That Maybe :: These (Type -> Type) a1) :: Morph (These (Type -> Type) a1)) (Flip These a2) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

type Morphing ('Into ('That Maybe :: These (Type -> Type) a1) :: Morph (These (Type -> Type) a1)) (Flip These a2) = Maybe
type Morphing ('Into Wye) ((:*:) <:.:> Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

type Morphing ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_U Covariant Covariant Identity (:*:) (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_U Covariant Covariant Identity (:*:) (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) (T_U Covariant Covariant (Construction Wye) (:*:) ((Biforked <:.> Construction Biforked) <:.> T_U Covariant Covariant Identity (:*:) (Maybe <:.> Construction Wye))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

rotate :: forall f t. Morphable (Rotate f) t => t ~> Morphing (Rotate f) t Source #

into :: forall f t. Morphable (Into f) t => t ~> Morphing (Into f) t Source #