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

Pandora.Paradigm.Structure.Ability.Morphable

Documentation

class Morphable (mod :: k) struct | mod struct -> struct where Source #

Associated Types

type Morphing (mod :: k) (struct :: * -> *) :: * -> * Source #

Methods

morphing :: (Tagged mod <::> struct) ~> Morphing mod struct Source #

Instances

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Delete 'All) List :: Type -> Type Source #

Morphable ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Delete 'First) List :: Type -> Type Source #

Morphable ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Find 'Element) List :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into (Construction Maybe)) (Vector r) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into List) (Vector r) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing ('Into List) (Vector r) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Into List) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into List) (Tape List) :: Type -> Type Source #

Morphable ('Into Binary) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Into Binary) (Construction (Maybe <:*:> Maybe)) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Right) (Tape Stream) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Left) (Tape Stream) :: Type -> Type Source #

Morphable ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Find 'Element) (Construction Maybe) :: 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.Structure

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.Structure

Associated Types

type Morphing ('Into ('This Maybe)) (These e2) :: 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 #

Setoid key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Lookup 'Key) (Prefixed List key) :: Type -> Type Source #

Setoid k => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Morphing ('Lookup 'Key) (Prefixed Rose k) :: Type -> Type Source #

Chain k => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Lookup 'Key) (Prefixed Binary k) :: 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.Structure

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.Structure

Associated Types

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into List) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Into List) (Construction Maybe <::> Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Setoid key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) ((Prefixed < Construction Maybe) < key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Lookup 'Key) ((Prefixed < Construction Maybe) < key) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Right) (Tape > Construction Maybe) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Left) (Tape > Construction Maybe) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Right) (Turnover < Tape List) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Left) (Turnover < Tape List) :: Type -> Type Source #

Chain key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) ((Prefixed < Construction (Maybe <:*:> Maybe)) < key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Lookup 'Key) ((Prefixed < Construction (Maybe <:*:> Maybe)) < key) :: Type -> Type Source #

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into > Tape List) List :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Comprehension Maybe) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into > Comprehension Maybe) (Tape List) :: Type -> Type Source #

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable (('Rotate :: Horizontal (a -> Splay a) -> Morph (Horizontal (a -> Splay a))) > 'Right ('Zig :: a -> Splay a) :: Morph (Horizontal (a -> Splay a))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Rotate :: Horizontal (a -> Splay a) -> Morph (Horizontal (a -> Splay a))) > 'Left ('Zig :: a -> Splay a) :: Morph (Horizontal (a -> Splay a))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Construction Maybe) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Pop :: a -> Morph a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing 'Pop List :: Type -> Type Source #

Morphable ('Push :: a -> Morph a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing 'Push List :: Type -> Type Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Monoidal (-->) (-->) (:*:) (:*:) t) => Morphable ('Push :: a -> Morph a) (Comprehension t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Associated Types

type Morphing 'Push (Comprehension t) :: Type -> Type Source #

Morphable ('Push :: a -> Morph a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

type Morphed mod struct result = (Morphable mod struct, Morphing mod struct ~ result) Source #

morph :: forall mod struct. Morphable mod struct => struct ~> Morphing mod struct Source #

premorph :: Morphable mod struct => (Tagged mod <::> struct) ~> struct 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 
Insert a 
Push a 
Pop a 
Delete a 
Find a 
Lookup a 
Vary a 
Key a 
Element a 

Instances

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Delete 'All) List :: Type -> Type Source #

Morphable ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Delete 'First) List :: Type -> Type Source #

Morphable ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Find 'Element) List :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into (Construction Maybe)) (Vector r) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into List) (Vector r) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

type Morphing ('Into List) (Vector r) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Into List) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into List) (Tape List) :: Type -> Type Source #

Morphable ('Into Binary) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Into Binary) (Construction (Maybe <:*:> Maybe)) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Right) (Tape Stream) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Left) (Tape Stream) :: Type -> Type Source #

Morphable ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Find 'Element) (Construction Maybe) :: 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.Structure

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.Structure

Associated Types

type Morphing ('Into ('This Maybe)) (These e2) :: 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 #

Setoid key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Lookup 'Key) (Prefixed List key) :: Type -> Type Source #

Setoid k => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Morphing ('Lookup 'Key) (Prefixed Rose k) :: Type -> Type Source #

Chain k => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Lookup 'Key) (Prefixed Binary k) :: 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.Structure

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.Structure

Associated Types

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

Morphable ('Into List) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Into List) (Construction Maybe <::> Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Setoid key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) ((Prefixed < Construction Maybe) < key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Lookup 'Key) ((Prefixed < Construction Maybe) < key) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Right) (Tape > Construction Maybe) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Left) (Tape > Construction Maybe) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Right) (Turnover < Tape List) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Left) (Turnover < Tape List) :: Type -> Type Source #

Chain key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) ((Prefixed < Construction (Maybe <:*:> Maybe)) < key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Lookup 'Key) ((Prefixed < Construction (Maybe <:*:> Maybe)) < key) :: Type -> Type Source #

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into > Tape List) List :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Comprehension Maybe) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into > Comprehension Maybe) (Tape List) :: Type -> Type Source #

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable (('Rotate :: Horizontal (a -> Splay a) -> Morph (Horizontal (a -> Splay a))) > 'Right ('Zig :: a -> Splay a) :: Morph (Horizontal (a -> Splay a))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Rotate :: Horizontal (a -> Splay a) -> Morph (Horizontal (a -> Splay a))) > 'Left ('Zig :: a -> Splay a) :: Morph (Horizontal (a -> Splay a))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

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

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Construction Maybe) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Pop :: a -> Morph a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing 'Pop List :: Type -> Type Source #

Morphable ('Push :: a -> Morph a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing 'Push List :: Type -> Type Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Monoidal (-->) (-->) (:*:) (:*:) t) => Morphable ('Push :: a -> Morph a) (Comprehension t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

Associated Types

type Morphing 'Push (Comprehension t) :: Type -> Type Source #

Morphable ('Push :: a -> Morph a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure

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

Defined in Pandora.Paradigm.Structure

type Morphing ('Into (Conclusion e) :: Morph (Type -> Type)) Maybe = ((->) e :: Type -> Type) <:.> Conclusion e
type Morphing ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List = (Predicate <:.:> List) >>>>>> ((->) :: Type -> Type -> Type)
type Morphing ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List = (Predicate <:.:> List) >>>>>> ((->) :: Type -> Type -> Type)
type Morphing ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) List = (Predicate <:.:> Maybe) >>>>>> ((->) :: Type -> Type -> Type)
type Morphing ('Into ('Left_ Maybe)) Wye Source # 
Instance details

Defined in Pandora.Paradigm.Structure

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

Defined in Pandora.Paradigm.Structure

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

Defined in Pandora.Paradigm.Structure

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

Defined in Pandora.Paradigm.Structure

type Morphing ('Into List) (Vector r) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

type Morphing ('Into List) (Vector r) = List
type Morphing ('Into List) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into List) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into Binary) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape Stream) = Tape Stream
type Morphing ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape Stream) = Tape Stream
type Morphing ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Find ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Construction Maybe) = (Predicate <:.:> Maybe) >>>>>> ((->) :: Type -> Type -> Type)
type Morphing ('Into ('There Maybe :: Wedge e1 (Type -> Type)) :: Morph (Wedge e1 (Type -> Type))) (Wedge e2) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

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.Structure

type Morphing ('Into ('This Maybe :: These e1 (Type -> Type)) :: Morph (These e1 (Type -> Type))) (These e2) = Maybe
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 ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed List key) = ((->) key :: Type -> Type) <::> Maybe
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) = ((->) (Nonempty List k) :: Type -> Type) <:.> Maybe
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) = ((->) k :: Type -> Type) <::> Maybe
type Morphing ('Into ('Here Maybe :: Wedge (Type -> Type) a1) :: Morph (Wedge (Type -> Type) a1)) (Flip Wedge a2) 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) = 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.Structure

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

Defined in Pandora.Paradigm.Structure

type Morphing ('Into List) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into List) (Construction Maybe <::> Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) ((Prefixed < Construction Maybe) < key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) ((Prefixed < Construction Maybe) < key) = ((->) key :: Type -> Type) <::> Maybe
type Morphing ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Right :: a -> Horizontal a) :: Morph (a -> Horizontal a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) = (Turnover :: (Type -> Type) -> Type -> Type) < Tape List
type Morphing ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Left :: a -> Horizontal a) :: Morph (a -> Horizontal a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) = (Turnover :: (Type -> Type) -> Type -> Type) < Tape List
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) ((Prefixed < Construction (Maybe <:*:> Maybe)) < key) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) ((Prefixed < Construction (Maybe <:*:> Maybe)) < key) = ((->) key :: Type -> Type) <::> Maybe
type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) List = Maybe <::> Tape List
type Morphing (('Rotate :: Horizontal (a -> Splay a) -> Morph (Horizontal (a -> Splay a))) > 'Right ('Zig :: a -> Splay a) :: Morph (Horizontal (a -> Splay a))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) Binary = Binary
type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Comprehension Maybe) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Comprehension Maybe) (Tape List) = Comprehension Maybe
type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) (Construction Maybe) = Tape List
type Morphing (('Rotate :: Horizontal (a -> Splay a) -> Morph (Horizontal (a -> Splay a))) > 'Right ('Zig :: a -> Splay a) :: Morph (Horizontal (a -> Splay a))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) = Maybe <::> Construction (Maybe <:*:> Maybe)
type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) = Maybe <::> Construction (Maybe <:*:> Maybe)
type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) = Maybe <::> Construction (Maybe <:*:> Maybe)
type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing (('Rotate :: Horizontal (Splay (a -> Splay a)) -> Morph (Horizontal (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Horizontal (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Horizontal (Splay (a -> Splay a)))) (Construction (Maybe <:*:> Maybe)) = Maybe <::> Construction (Maybe <:*:> Maybe)
type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Construction Maybe) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Construction Maybe) (Tape > Construction Maybe) = Construction Maybe
type Morphing ('Pop :: a -> Morph a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Pop :: a -> Morph a) List = List
type Morphing ('Push :: a -> Morph a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Push :: a -> Morph a) List = (Exactly <:.:> List) >>>>>> ((->) :: Type -> Type -> Type)
type Morphing ('Push :: a -> Morph a) (Comprehension t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Comprehension

type Morphing ('Push :: a -> Morph a) (Comprehension t) = (Exactly <:.:> Comprehension t) >>>>>> ((->) :: Type -> Type -> Type)
type Morphing ('Push :: a -> Morph a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Push :: a -> Morph a) (Construction Maybe) = (Exactly <:.:> Construction Maybe) >>>>>> ((->) :: Type -> Type -> Type)

data Occurrence a Source #

Constructors

All a 
First a 

Instances

Instances details
Morphable ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Delete 'All) List :: Type -> Type Source #

Morphable ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Delete 'First) List :: Type -> Type Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal (-->) (:*:) (:*:) t) => Substructure ('All ('Right :: a -> Horizontal a) :: Occurrence (a -> Horizontal a)) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

type Substance ('All 'Right) (Tape t <::> Tape t) :: Type -> Type Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal (-->) (:*:) (:*:) t) => Substructure ('All ('Left :: a -> Horizontal a) :: Occurrence (a -> Horizontal a)) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

type Substance ('All 'Left) (Tape t <::> Tape t) :: Type -> Type Source #

type Morphing ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Delete ('All :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List = (Predicate <:.:> List) >>>>>> ((->) :: Type -> Type -> Type)
type Morphing ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Delete ('First :: a -> Occurrence a) :: Morph (a -> Occurrence a)) List = (Predicate <:.:> List) >>>>>> ((->) :: Type -> Type -> Type)
type Substance ('All ('Right :: a -> Horizontal a) :: Occurrence (a -> Horizontal a)) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

type Substance ('All ('Right :: a -> Horizontal a) :: Occurrence (a -> Horizontal a)) (Tape t <::> Tape t) = Tape t <::> t
type Substance ('All ('Left :: a -> Horizontal a) :: Occurrence (a -> Horizontal a)) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

type Substance ('All ('Left :: a -> Horizontal a) :: Occurrence (a -> Horizontal a)) (Tape t <::> Tape t) = Tape t <::> Reverse t

rotate :: forall mod struct. Morphable (Rotate mod) struct => struct ~> Morphing (Rotate mod) struct Source #

into :: forall mod struct. Morphable (Into mod) struct => struct ~> Morphing (Into mod) struct Source #

insert :: forall mod struct a. Morphed (Insert mod) struct ((Exactly <:.:> struct) >>>>>> (->)) => a :=:=> struct Source #

item :: forall mod struct a. Morphed mod struct ((Exactly <:.:> struct) >>>>>> (->)) => a :=:=> struct Source #

collate :: forall mod struct a. (Chain a, Morphed mod struct ((((Exactly <:.:> Comparison) >>>>>> (:*:)) <:.:> struct) >>>>>> (->))) => a :=:=> struct Source #

delete :: forall mod struct a. (Setoid a, Morphed (Delete mod) struct ((Predicate <:.:> struct) >>>>>> (->))) => a :=:=> struct Source #

filter :: forall mod struct a. Morphed (Delete mod) struct ((Predicate <:.:> struct) >>>>>> (->)) => Predicate a -> struct a -> struct a Source #

find :: forall mod struct result a. Morphed (Find mod) struct ((Predicate <:.:> result) >>>>>> (->)) => Predicate a -> struct a -> result a Source #

lookup :: forall mod key struct a. Morphed (Lookup mod) struct ((->) key <::> Maybe) => key -> struct a -> Maybe a Source #

vary :: forall mod key value struct. Morphed (Vary mod) struct ((((:*:) key <::> Exactly) <:.:> struct) >>>>>>> (->)) => key -> value -> struct value -> struct value Source #