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

Pandora.Paradigm.Primary.Functor.Maybe

Documentation

data Maybe a Source #

Constructors

Nothing 
Just a 

Instances

Instances details
Zippable List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Breadcrumbs List :: Type -> Type Source #

Stack List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Topping List :: Type -> Type Source #

type Popping List :: Type -> Type Source #

type Pushing List :: Type -> Type Source #

Methods

top :: Lens (Topping List) (List e) e Source #

pop :: State (Popping List e) (Maybe e) Source #

push :: e -> State (Pushing List e) e Source #

Lensic Exactly Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Associated Types

type Lensally Exactly Maybe :: Type -> Type Source #

Methods

(>>>) :: Lens Exactly source between -> Lens Maybe between target -> Lens (Lensally Exactly Maybe) source target Source #

Lensic Maybe Exactly Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Associated Types

type Lensally Maybe Exactly :: Type -> Type Source #

Methods

(>>>) :: Lens Maybe source between -> Lens Exactly between target -> Lens (Lensally Maybe Exactly) source target Source #

Zoomable State Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Inventory

Methods

zoom :: forall bg ls (t :: Type -> Type). Adaptable t (->) (State bg) => Lens Maybe bg ls -> State (Simplification Maybe ls) ~> t Source #

Monoidal (-->) (-->) (:*:) (:+:) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

unit :: Proxy (:*:) -> (Unit (:+:) --> a) --> Maybe a Source #

Monoidal (-->) (-->) (:*:) (:*:) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) --> Maybe a Source #

Monotonic a (Maybe a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

reduce :: (a -> r -> r) -> r -> Maybe a -> r Source #

resolve :: (a -> r) -> r -> Maybe a -> r Source #

Accessible target source => Possible target (Maybe source) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Methods

perhaps :: Lens Maybe (Maybe source) target Source #

Possible a (Maybe a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Methods

perhaps :: Lens Maybe (Maybe a) a Source #

Monotonic a (t a) => Monotonic a ((Maybe :. t) > a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

reduce :: (a -> r -> r) -> r -> ((Maybe :. t) > a) -> r Source #

resolve :: (a -> r) -> r -> ((Maybe :. t) > a) -> r Source #

Semigroup a => Semigroup (Maybe a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

(+) :: Maybe a -> Maybe a -> Maybe a Source #

Semigroup (List a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(+) :: List a -> List a -> List a Source #

Semigroup a => Monoid (Maybe a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

zero :: Maybe a Source #

Monoid (List a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

zero :: List a Source #

Supremum a => Supremum (Maybe a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

(\/) :: Maybe a -> Maybe a -> Maybe a Source #

Infimum a => Infimum (Maybe a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

(/\) :: Maybe a -> Maybe a -> Maybe a Source #

Lattice a => Lattice (Maybe a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Setoid a => Setoid (Maybe a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

(==) :: Maybe a -> Maybe a -> Boolean Source #

(!=) :: Maybe a -> Maybe a -> Boolean Source #

(?=) :: Maybe a -> Maybe a -> r -> r -> r Source #

Setoid a => Setoid (List a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(==) :: List a -> List a -> Boolean Source #

(!=) :: List a -> List a -> Boolean Source #

(?=) :: List a -> List a -> r -> r -> r Source #

Chain a => Chain (Maybe a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

(<=>) :: Maybe a -> Maybe a -> Ordering Source #

(<) :: Maybe a -> Maybe a -> Boolean Source #

(<=) :: Maybe a -> Maybe a -> Boolean Source #

(>) :: Maybe a -> Maybe a -> Boolean Source #

(>=) :: Maybe a -> Maybe a -> Boolean Source #

Semigroupoid (Lens Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Methods

(.) :: Lens Maybe b c -> Lens Maybe a b -> Lens Maybe a c Source #

Category (Lens Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Zippable (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Breadcrumbs (Construction Maybe) :: Type -> Type Source #

Zippable (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Breadcrumbs (Construction List) :: Type -> Type Source #

Zippable (Comprehension Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Breadcrumbs (Comprehension Maybe) :: Type -> Type Source #

Stack (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Topping (Construction Maybe) :: Type -> Type Source #

type Popping (Construction Maybe) :: Type -> Type Source #

type Pushing (Construction Maybe) :: Type -> Type Source #

Semimonoidal (-->) (:*:) (:+:) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

mult :: forall (a :: k) (b :: k). (Maybe a :*: Maybe b) --> Maybe (a :+: b) Source #

Semimonoidal (-->) (:*:) (:*:) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

mult :: forall (a :: k) (b :: k). (Maybe a :*: Maybe b) --> Maybe (a :*: b) Source #

Semimonoidal (<--) (:*:) (:*:) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

mult :: forall (a :: k) (b :: k). (Maybe a :*: Maybe b) <-- Maybe (a :*: b) Source #

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 #

Substructure ('Right ('Branch :: a -> Segment a) :: Wye (a -> Segment a)) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Substance ('Right 'Branch) Binary :: Type -> Type Source #

Substructure ('Left ('Branch :: a -> Segment a) :: Wye (a -> Segment a)) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Substance ('Left 'Branch) Binary :: Type -> Type Source #

Morphable ('Into (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) :: Morph (Type -> Type)) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Morphing ('Into (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))))) (Construction List) :: 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 ('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 #

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 #

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 #

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 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 ('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 #

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 #

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 -> Wye a) :: Morph (a -> Wye 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 -> Wye a) :: Morph (a -> Wye 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 -> Wye a) :: Morph (a -> Wye 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 -> Wye a) :: Morph (a -> Wye 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 #

Morphable ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Morphing ('Rotate 'Up) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) :: Type -> Type Source #

Substructure ('Right ('Forest :: a -> Segment a) :: Wye (a -> Segment a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Right 'Forest) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) :: Type -> Type Source #

Substructure ('Left ('Forest :: a -> Segment a) :: Wye (a -> Segment a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Left 'Forest) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) :: Type -> Type Source #

Substructure ('Down ('Forest :: a -> Segment a) :: Vertical (a -> Segment a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Down 'Forest) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) :: Type -> Type Source #

Substructure ('Up ('Forest :: a -> Segment a) :: Vertical (a -> Segment a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Up 'Forest) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) :: 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 :: Wye (a -> Splay a) -> Morph (Wye (a -> Splay a))) > 'Right ('Zig :: a -> Splay a) :: Morph (Wye (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 :: Wye (a -> Splay a) -> Morph (Wye (a -> Splay a))) > 'Left ('Zig :: a -> Splay a) :: Morph (Wye (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 :: Wye (Splay (a -> Splay a)) -> Morph (Wye (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Wye (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Wye (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 :: Wye (Splay (a -> Splay a)) -> Morph (Wye (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Wye (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Wye (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 :: Wye (Splay (a -> Splay a)) -> Morph (Wye (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Wye (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Wye (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 :: Wye (Splay (a -> Splay a)) -> Morph (Wye (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Wye (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Wye (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 :: Wye (a -> Splay a) -> Morph (Wye (a -> Splay a))) > 'Right ('Zig :: a -> Splay a) :: Morph (Wye (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 :: Wye (a -> Splay a) -> Morph (Wye (a -> Splay a))) > 'Left ('Zig :: a -> Splay a) :: Morph (Wye (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 :: Wye (Splay (a -> Splay a)) -> Morph (Wye (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Wye (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Wye (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 :: Wye (Splay (a -> Splay a)) -> Morph (Wye (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Wye (Splay (a -> Splay a))) > 'Zig ('Zag :: a -> Splay a)) :: Morph (Wye (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 :: Wye (Splay (a -> Splay a)) -> Morph (Wye (Splay (a -> Splay a)))) > (('Right :: Splay (a -> Splay a) -> Wye (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Wye (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 :: Wye (Splay (a -> Splay a)) -> Morph (Wye (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Wye (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Wye (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 #

Impliable (P_Q_T ((->) :: Type -> Type -> Type) Store Maybe source target :: Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Associated Types

type Arguments (P_Q_T (->) Store Maybe source target) = (args :: Type) Source #

Methods

imply :: Arguments (P_Q_T (->) Store Maybe source target) Source #

Semigroup (Construction Maybe a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Bindable ((->) :: Type -> Type -> Type) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

(=<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source #

(==<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source #

(===<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source #

(====<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source #

(=====<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source #

(======<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source #

(=======<<) :: (a -> Maybe b) -> Maybe a -> Maybe b Source #

Interpreted ((->) :: Type -> Type -> Type) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Associated Types

type Primary Maybe a Source #

Methods

run :: ((->) < Maybe a) < Primary Maybe a Source #

unite :: ((->) < Primary Maybe a) < Maybe a Source #

(<~~~~~~~~) :: ((->) < Maybe a) < Primary Maybe a Source #

(<~~~~~~~) :: ((->) < Maybe a) < Primary Maybe a Source #

(<~~~~~~) :: ((->) < Maybe a) < Primary Maybe a Source #

(<~~~~~) :: ((->) < Maybe a) < Primary Maybe a Source #

(<~~~~) :: ((->) < Maybe a) < Primary Maybe a Source #

(<~~~) :: ((->) < Maybe a) < Primary Maybe a Source #

(<~~) :: ((->) < Maybe a) < Primary Maybe a Source #

(<~) :: ((->) < Maybe a) < Primary Maybe a Source #

(=#-) :: (Semigroupoid (->), Interpreted (->) u) => (((->) < Primary Maybe a) < Primary u b) -> ((->) < Maybe a) < u b Source #

(-#=) :: (Semigroupoid (->), Interpreted (->) u) => (((->) < Maybe a) < u b) -> ((->) < Primary Maybe a) < Primary u b Source #

(<$=#-) :: (Semigroupoid (->), Covariant (->) (->) j, Interpreted (->) u) => (((->) < Primary Maybe a) < Primary u b) -> (j > Maybe a) -> (j > u b) Source #

(-#=$>) :: (Covariant (->) (->) j, Interpreted (->) u) => (((->) < Maybe a) < u b) -> (j > Primary Maybe a) -> (j > Primary u b) Source #

Monadic ((->) :: Type -> Type -> Type) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

wrap :: forall (u :: Type -> Type) a. Pointable u => ((->) < Maybe a) < (Maybe :> u) a Source #

Gettable (Lens Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

Associated Types

type Getting (Lens Maybe) e r Source #

Methods

get :: Getting (Lens Maybe) e r 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 #

Substructure ('Rest :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substance 'Rest List :: Type -> Type Source #

Substructure ('Root :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substance 'Root List :: 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 #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

(<-|-) :: (a -> b) -> Maybe a -> Maybe b Source #

(<-|--) :: (a -> b) -> Maybe a -> Maybe b Source #

(<-|---) :: (a -> b) -> Maybe a -> Maybe b Source #

(<-|----) :: (a -> b) -> Maybe a -> Maybe b Source #

(<-|-----) :: (a -> b) -> Maybe a -> Maybe b Source #

(<-|------) :: (a -> b) -> Maybe a -> Maybe b Source #

(<-|-------) :: (a -> b) -> Maybe a -> Maybe b Source #

(<-|--------) :: (a -> b) -> Maybe a -> Maybe b Source #

(<-|-|-) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) Maybe) => (a -> b) -> Maybe (u a) -> Maybe (u b) Source #

(<-|-|--) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) Maybe) => (a -> b) -> Maybe (u a) -> Maybe (u b) Source #

(<-|-|---) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) Maybe) => (a -> b) -> Maybe (u a) -> Maybe (u b) Source #

(<-|-|----) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) Maybe) => (a -> b) -> Maybe (u a) -> Maybe (u b) Source #

(<-|-|-----) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) Maybe) => (a -> b) -> Maybe (u a) -> Maybe (u b) Source #

(<-|-|------) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) Maybe) => (a -> b) -> Maybe (u a) -> Maybe (u b) Source #

(<-|-|-------) :: (Covariant (->) (Betwixt (->) (->)) u, Covariant (Betwixt (->) (->)) (->) Maybe) => (a -> b) -> Maybe (u a) -> Maybe (u b) Source #

(<-|-|-|-) :: (Covariant (->) (Betwixt (->) (Betwixt (->) (->))) v, Covariant (Betwixt (->) (Betwixt (->) (->))) (Betwixt (Betwixt (->) (->)) (->)) u, Covariant (Betwixt (Betwixt (->) (->)) (->)) (->) Maybe) => (a -> b) -> Maybe (u (v a)) -> Maybe (u (v b)) Source #

Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

(<<-) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Maybe a -> u (Maybe b) Source #

(<<-------) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Maybe a -> u (Maybe b) Source #

(<<------) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Maybe a -> u (Maybe b) Source #

(<<-----) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Maybe a -> u (Maybe b) Source #

(<<----) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Maybe a -> u (Maybe b) Source #

(<<---) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Maybe a -> u (Maybe b) Source #

(<<--) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Maybe a -> u (Maybe b) Source #

Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(<<-) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<<-------) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<<------) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<<-----) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<<----) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<<---) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<<--) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

type Nonempty Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Nonempty List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Nonempty Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Combinative List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Breadcrumbs List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Topping List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Popping List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Pushing List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Primary Maybe a Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

type Primary Maybe a = Maybe a
type Lensally Exactly Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

type Lensally Maybe Exactly Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

type Schematic Monad Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

type Breadcrumbs (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Breadcrumbs (Construction Maybe) = (Reverse :: (Type -> Type) -> Type -> Type) > (Construction Maybe <:*:> Construction Maybe)
type Breadcrumbs (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Breadcrumbs (Comprehension Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Topping (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Popping (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Pushing (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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 Substance ('Right ('Branch :: a -> Segment a) :: Wye (a -> Segment a)) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substance ('Right ('Branch :: a -> Segment a) :: Wye (a -> Segment a)) Binary = Binary
type Substance ('Left ('Branch :: a -> Segment a) :: Wye (a -> Segment a)) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substance ('Left ('Branch :: a -> Segment a) :: Wye (a -> Segment a)) Binary = Binary
type Morphing ('Into (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) :: Morph (Type -> Type)) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

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 ('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 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 ('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 ('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 Binary) (Construction > (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

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 <:*:> 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 ('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 -> Wye a) :: Morph (a -> Wye a)) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) = (Turnover :: (Type -> Type) -> Type -> Type) < Tape List
type Morphing ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Right ('Forest :: a -> Segment a) :: Wye (a -> Segment a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Left ('Forest :: a -> Segment a) :: Wye (a -> Segment a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Down ('Forest :: a -> Segment a) :: Vertical (a -> Segment a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Up ('Forest :: a -> Segment a) :: Vertical (a -> Segment a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

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 :: Wye (a -> Splay a) -> Morph (Wye (a -> Splay a))) > 'Right ('Zig :: a -> Splay a) :: Morph (Wye (a -> Splay a))) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing (('Rotate :: Wye (Splay (a -> Splay a)) -> Morph (Wye (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Wye (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Wye (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 :: Wye (a -> Splay a) -> Morph (Wye (a -> Splay a))) > 'Right ('Zig :: a -> Splay a) :: Morph (Wye (a -> Splay a))) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

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

Defined in Pandora.Paradigm.Structure.Some.Splay

type Morphing (('Rotate :: Wye (Splay (a -> Splay a)) -> Morph (Wye (Splay (a -> Splay a)))) > (('Left :: Splay (a -> Splay a) -> Wye (Splay (a -> Splay a))) > 'Zig ('Zig :: a -> Splay a)) :: Morph (Wye (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 Arguments (P_Q_T ((->) :: Type -> Type -> Type) Store Maybe source target :: Type) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

type Arguments (P_Q_T ((->) :: Type -> Type -> Type) Store Maybe source target :: Type) = (source -> Maybe target) -> (source -> Maybe target -> source) -> Lens Maybe source target
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 Substance ('Rest :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substance ('Rest :: a -> Segment a) List = List
type Substance ('Root :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substance ('Root :: a -> Segment a) List = Maybe
type Getting (Lens Maybe) source target Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Some.Optics

type Getting (Lens Maybe) source target = Lens Maybe source target -> source -> Maybe target
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)

type Optional t = Adaptable t (->) Maybe Source #

nothing :: Optional t => t a Source #