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

Pandora.Paradigm.Structure.Ability.Morphable

Documentation

class Morphable f t | f t -> 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 (Flip Conclusion e) :: Morph (Type -> Type)) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

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

Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) List :: Type -> Type Source #

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 ('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 (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 (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)))) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: 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 List) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Into List) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into List) (Tap ((List <:.:> List) := (:*:))) :: 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 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 <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Left) (Tap ((List <:.:> List) := (:*:))) :: 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 #

Setoid k => Morphable ('Lookup ('Element :: 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 'Element) (Prefixed Rose 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.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 <:.:> Maybe) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

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

Morphable ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate 'Up) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

Morphable ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate ('Down 'Right)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

Morphable ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate ('Down 'Left)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: 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 #

Morphable ('Insert :: a -> Morph a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing 'Insert Binary :: Type -> Type Source #

Pointable 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 #

Morphable ('Insert :: a -> Morph a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

premorph :: Morphable f t => (Tagged f <:.> t) ~> 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 
Insert a 
Push a 
Pop a 
Delete a 
Find a 
Lookup a 
Element a 

Instances

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

Defined in Pandora.Paradigm.Primary

Associated Types

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

Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into (Tap ((List <:.:> List) := (:*:)))) List :: Type -> Type Source #

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 ('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 (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 (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)))) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Into (Tap ((List <:.:> List) := (:*:)))) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into (Construction Maybe)) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: 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 List) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Morphable ('Into List) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into List) (Tap ((List <:.:> List) := (:*:))) :: 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 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 <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Left) (Tap ((List <:.:> List) := (:*:))) :: 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 #

Setoid k => Morphable ('Lookup ('Element :: 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 'Element) (Prefixed Rose 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.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 <:.:> Maybe) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

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

Morphable ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate 'Up) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

Morphable ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate ('Down 'Right)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: Type -> Type Source #

Morphable ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Rotate ('Down 'Left)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) :: 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 #

Morphable ('Insert :: a -> Morph a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing 'Insert Binary :: Type -> Type Source #

Pointable 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 #

Morphable ('Insert :: a -> Morph a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.Primary

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

Defined in Pandora.Paradigm.Structure.Some.List

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 ('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 (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 (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)))) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Primary

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

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Into List) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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 <:.:> Stream) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

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

Defined in Pandora.Paradigm.Structure.Some.Stream

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tap ((List <:.:> List) := (:*:))) = Maybe <:.> Zipper List
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 ('Lookup ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Morphing ('Lookup ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) = ((->) (Nonempty List 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.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 <:.:> Maybe) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

type Morphing ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Down ('Right :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Rotate ('Down ('Left :: a -> Wye a)) :: Morph (Vertical (a -> Wye a))) ((Construction Wye <:.:> (Bifurcation <:.> Bicursor)) := (:*:)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

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 = (Identity <:.:> List) := ((->) :: Type -> Type -> Type)
type Morphing ('Insert :: a -> Morph a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Insert :: a -> Morph a) Binary = (((Identity <:.:> Comparison) := (:*:)) <:.:> Binary) := ((->) :: 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) = (Identity <:.:> 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) = (Identity <:.:> Construction Maybe) := ((->) :: Type -> Type -> Type)
type Morphing ('Insert :: a -> Morph a) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Insert :: a -> Morph a) (Construction Wye) = (((Identity <:.:> Comparison) := (:*:)) <:.:> Construction Wye) := ((->) :: 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 #

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)

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 #

insert :: forall f t a. (Morphable (Insert f) t, Morphing (Insert f) t ~ ((Identity <:.:> t) := (->))) => a :=:=> t Source #

item :: forall f t a. (Morphable f t, Morphing f t ~ ((Identity <:.:> t) := (->))) => a :=:=> t Source #

collate :: forall f t a. (Chain a, Morphable f t, Morphing f t ~ ((((Identity <:.:> Comparison) := (:*:)) <:.:> t) := (->))) => a :=:=> t Source #

delete :: forall f t a. (Setoid a, Morphable (Delete f) t, Morphing (Delete f) t ~ ((Predicate <:.:> t) := (->))) => a :=:=> t Source #

filter :: forall f t a. (Morphable (Delete f) t, Morphing (Delete f) t ~ ((Predicate <:.:> t) := (->))) => Predicate a -> t a -> t a Source #

find :: forall f t u a. (Morphable (Find f) t, Morphing (Find f) t ~ ((Predicate <:.:> u) := (->))) => Predicate a -> t a -> u a Source #