pandora-0.4.1: 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
Covariant Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

comap :: (a -> b) -> Maybe a -> Maybe b Source #

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

($>) :: Maybe a -> b -> Maybe b Source #

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

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

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

(<$$>) :: Covariant u => (a -> b) -> ((Maybe :. u) := a) -> (Maybe :. u) := b Source #

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

(<$$$$>) :: (Covariant u, Covariant v, Covariant w) => (a -> b) -> ((Maybe :. (u :. (v :. w))) := a) -> (Maybe :. (u :. (v :. w))) := b Source #

(<&&>) :: Covariant u => ((Maybe :. u) := a) -> (a -> b) -> (Maybe :. u) := b Source #

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

(<&&&&>) :: (Covariant u, Covariant v, Covariant w) => ((Maybe :. (u :. (v :. w))) := a) -> (a -> b) -> (Maybe :. (u :. (v :. w))) := b Source #

(.#..) :: (Maybe ~ v a, Category v) => v c d -> ((v a :. v b) := c) -> (v a :. v b) := d Source #

(.#...) :: (Maybe ~ v a, Maybe ~ v b, Category v, Covariant (v a), Covariant (v b)) => v d e -> ((v a :. (v b :. v c)) := d) -> (v a :. (v b :. v c)) := e Source #

(.#....) :: (Maybe ~ v a, Maybe ~ v b, Maybe ~ v c, Category v, Covariant (v a), Covariant (v b), Covariant (v c)) => v e f -> ((v a :. (v b :. (v c :. v d))) := e) -> (v a :. (v b :. (v c :. v d))) := f Source #

(<$$) :: Covariant u => b -> ((Maybe :. u) := a) -> (Maybe :. u) := b Source #

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

(<$$$$) :: (Covariant u, Covariant v, Covariant w) => b -> ((Maybe :. (u :. (v :. w))) := a) -> (Maybe :. (u :. (v :. w))) := b Source #

($$>) :: Covariant u => ((Maybe :. u) := a) -> b -> (Maybe :. u) := b Source #

($$$>) :: (Covariant u, Covariant v) => ((Maybe :. (u :. v)) := a) -> b -> (Maybe :. (u :. v)) := b Source #

($$$$>) :: (Covariant u, Covariant v, Covariant w) => ((Maybe :. (u :. (v :. w))) := a) -> b -> (Maybe :. (u :. (v :. w))) := b Source #

Bindable Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

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

bind :: (a -> Maybe b) -> Maybe a -> Maybe b Source #

join :: ((Maybe :. Maybe) := a) -> Maybe a Source #

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

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

($>>=) :: Covariant u => ((u :. Maybe) := a) -> (a -> Maybe b) -> (u :. Maybe) := b Source #

Applicative Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

apply :: Maybe (a -> b) -> Maybe a -> Maybe b Source #

(*>) :: Maybe a -> Maybe b -> Maybe b Source #

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

forever :: Maybe a -> Maybe b Source #

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

(<**>) :: Applicative u => ((Maybe :. u) := (a -> b)) -> ((Maybe :. u) := a) -> (Maybe :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Maybe :. (u :. v)) := (a -> b)) -> ((Maybe :. (u :. v)) := a) -> (Maybe :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Maybe :. (u :. (v :. w))) := (a -> b)) -> ((Maybe :. (u :. (v :. w))) := a) -> (Maybe :. (u :. (v :. w))) := b Source #

Alternative Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

alter :: Maybe a -> Maybe a -> Maybe a Source #

Avoidable Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

empty :: Maybe a Source #

Pointable Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

point :: a :=> Maybe Source #

pass :: Maybe () Source #

Monad Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

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

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

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

Traversable Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

(->>) :: (Pointable u, Applicative u) => Maybe a -> (a -> u b) -> (u :. Maybe) := b Source #

traverse :: (Pointable u, Applicative u) => (a -> u b) -> Maybe a -> (u :. Maybe) := b Source #

sequence :: (Pointable u, Applicative u) => ((Maybe :. u) := a) -> (u :. Maybe) := a Source #

(->>>) :: (Pointable u, Applicative u, Traversable v) => ((v :. Maybe) := a) -> (a -> u b) -> (u :. (v :. Maybe)) := b Source #

(->>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w) => ((w :. (v :. Maybe)) := a) -> (a -> u b) -> (u :. (w :. (v :. Maybe))) := b Source #

(->>>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w, Traversable j) => ((j :. (w :. (v :. Maybe))) := a) -> (a -> u b) -> (u :. (j :. (w :. (v :. Maybe)))) := b Source #

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

(||=) :: Interpreted u => (Primary Maybe a -> Primary u b) -> Maybe a -> u b Source #

(=||) :: Interpreted u => (Maybe a -> u b) -> Primary Maybe a -> Primary u b Source #

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

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

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

(<$$$$||=) :: (Covariant j, Covariant k, Covariant l, Covariant m, Interpreted u) => (Primary Maybe a -> Primary u b) -> ((j :. (k :. (l :. m))) := Maybe a) -> (j :. (k :. (l :. m))) := u b Source #

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

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

(=||$$$>) :: (Covariant j, Covariant k, Covariant l, Interpreted u) => (Maybe a -> u b) -> ((j :. (k :. l)) := Primary Maybe a) -> (j :. (k :. l)) := Primary u b Source #

(=||$$$$>) :: (Covariant j, Covariant k, Covariant l, Covariant m, Interpreted u) => (Maybe a -> u b) -> ((j :. (k :. (l :. m))) := Primary Maybe a) -> (j :. (k :. (l :. m))) := Primary u b Source #

Monadic Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Methods

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

Stack List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Measurable 'Length List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Measural 'Length List a Source #

Measurable 'Heighth Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Measural 'Heighth Binary a Source #

Measurable 'Length (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Measural 'Length (Construction 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 #

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 #

Applicative (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(<*>) :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) (a -> b) -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b Source #

apply :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) (a -> b) -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b Source #

(*>) :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b Source #

(<*) :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a Source #

forever :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b Source #

(<%>) :: Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) a -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) (a -> b) -> Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) b Source #

(<**>) :: Applicative u => ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. u) := (a -> b)) -> ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. u) := a) -> (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. v)) := (a -> b)) -> ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. v)) := a) -> (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. (v :. w))) := (a -> b)) -> ((Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. (v :. w))) := a) -> (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:)) :. (u :. (v :. w))) := b Source #

Applicative (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(<*>) :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) (a -> b) -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b Source #

apply :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) (a -> b) -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b Source #

(*>) :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b Source #

(<*) :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a Source #

forever :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b Source #

(<%>) :: Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) a -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) (a -> b) -> Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) b Source #

(<**>) :: Applicative u => ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. u) := (a -> b)) -> ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. u) := a) -> (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. v)) := (a -> b)) -> ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. v)) := a) -> (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. (v :. w))) := (a -> b)) -> ((Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. (v :. w))) := a) -> (Tap ((Comprehension Maybe <:.:> Comprehension Maybe) := (:*:)) :. (u :. (v :. w))) := b Source #

Applicative (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(<*>) :: Tap ((List <:.:> List) := (:*:)) (a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

apply :: Tap ((List <:.:> List) := (:*:)) (a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

(*>) :: Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b -> Tap ((List <:.:> List) := (:*:)) b Source #

(<*) :: Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b -> Tap ((List <:.:> List) := (:*:)) a Source #

forever :: Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

(<%>) :: Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) (a -> b) -> Tap ((List <:.:> List) := (:*:)) b Source #

(<**>) :: Applicative u => ((Tap ((List <:.:> List) := (:*:)) :. u) := (a -> b)) -> ((Tap ((List <:.:> List) := (:*:)) :. u) := a) -> (Tap ((List <:.:> List) := (:*:)) :. u) := b Source #

(<***>) :: (Applicative u, Applicative v) => ((Tap ((List <:.:> List) := (:*:)) :. (u :. v)) := (a -> b)) -> ((Tap ((List <:.:> List) := (:*:)) :. (u :. v)) := a) -> (Tap ((List <:.:> List) := (:*:)) :. (u :. v)) := b Source #

(<****>) :: (Applicative u, Applicative v, Applicative w) => ((Tap ((List <:.:> List) := (:*:)) :. (u :. (v :. w))) := (a -> b)) -> ((Tap ((List <:.:> List) := (:*:)) :. (u :. (v :. w))) := a) -> (Tap ((List <:.:> List) := (:*:)) :. (u :. (v :. w))) := b Source #

Extendable (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(=>>) :: Tap ((List <:.:> List) := (:*:)) a -> (Tap ((List <:.:> List) := (:*:)) a -> b) -> Tap ((List <:.:> List) := (:*:)) b Source #

(<<=) :: (Tap ((List <:.:> List) := (:*:)) a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

extend :: (Tap ((List <:.:> List) := (:*:)) a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> Tap ((List <:.:> List) := (:*:)) b Source #

duplicate :: Tap ((List <:.:> List) := (:*:)) a -> (Tap ((List <:.:> List) := (:*:)) :. Tap ((List <:.:> List) := (:*:))) := a Source #

(=<=) :: (Tap ((List <:.:> List) := (:*:)) b -> c) -> (Tap ((List <:.:> List) := (:*:)) a -> b) -> Tap ((List <:.:> List) := (:*:)) a -> c Source #

(=>=) :: (Tap ((List <:.:> List) := (:*:)) a -> b) -> (Tap ((List <:.:> List) := (:*:)) b -> c) -> Tap ((List <:.:> List) := (:*:)) a -> c Source #

($=>>) :: Covariant u => ((u :. Tap ((List <:.:> List) := (:*:))) := a) -> (Tap ((List <:.:> List) := (:*:)) a -> b) -> (u :. Tap ((List <:.:> List) := (:*:))) := b Source #

(<<=$) :: Covariant u => ((u :. Tap ((List <:.:> List) := (:*:))) := a) -> (Tap ((List <:.:> List) := (:*:)) a -> b) -> (u :. Tap ((List <:.:> List) := (:*:))) := b Source #

Traversable (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Traversable (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(->>) :: (Pointable u, Applicative u) => Tap ((List <:.:> List) := (:*:)) a -> (a -> u b) -> (u :. Tap ((List <:.:> List) := (:*:))) := b Source #

traverse :: (Pointable u, Applicative u) => (a -> u b) -> Tap ((List <:.:> List) := (:*:)) a -> (u :. Tap ((List <:.:> List) := (:*:))) := b Source #

sequence :: (Pointable u, Applicative u) => ((Tap ((List <:.:> List) := (:*:)) :. u) := a) -> (u :. Tap ((List <:.:> List) := (:*:))) := a Source #

(->>>) :: (Pointable u, Applicative u, Traversable v) => ((v :. Tap ((List <:.:> List) := (:*:))) := a) -> (a -> u b) -> (u :. (v :. Tap ((List <:.:> List) := (:*:)))) := b Source #

(->>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w) => ((w :. (v :. Tap ((List <:.:> List) := (:*:)))) := a) -> (a -> u b) -> (u :. (w :. (v :. Tap ((List <:.:> List) := (:*:))))) := b Source #

(->>>>>) :: (Pointable u, Applicative u, Traversable v, Traversable w, Traversable j) => ((j :. (w :. (v :. Tap ((List <:.:> List) := (:*:))))) := a) -> (a -> u b) -> (u :. (j :. (w :. (v :. Tap ((List <:.:> List) := (:*:)))))) := b 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 #

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 #

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 #

Nullable Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Methods

null :: forall (a :: k). (Predicate :. Maybe) := a Source #

Nullable List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

null :: forall (a :: k). (Predicate :. List) := a Source #

Nullable Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Methods

null :: forall (a :: k). (Predicate :. Rose) := a Source #

Nullable Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Methods

null :: forall (a :: k). (Predicate :. Binary) := a Source #

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 (Construction Maybe)) (Vector r) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

Associated Types

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Defined in Pandora.Paradigm.Primary.Linear.Vector

Associated Types

type Morphing ('Into List) (Vector r) :: 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 ((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 ('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.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 ('Into ('Preorder (Construction Maybe))) (Construction Wye) Source # 
Instance details

Defined in Pandora.Paradigm.Structure

Associated Types

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

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

Defined in Pandora.Paradigm.Structure

Associated Types

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

Setoid key => Morphable ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (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 #

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 ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction List) k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Morphing ('Vary 'Element) (Prefixed (Construction List) k) :: Type -> Type Source #

Setoid k => Morphable ('Vary ('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 ('Vary 'Element) (Prefixed Rose k) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Morphing ('Vary 'Element) (Prefixed Binary k) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

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

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

Defined in Pandora.Paradigm.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 #

Semigroup (Construction Maybe a) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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 #

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substructural 'Tail List :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substructural 'Root List :: Type -> Type Source #

Substructure ('Just :: a -> Maybe a) Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substructural 'Just Rose :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substructural 'Root Rose :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Substructural 'Right Binary :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Binary

Associated Types

type Substructural 'Left Binary :: 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 #

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Substructure ('Root :: a -> Segment a) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substructural 'Root (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substructural 'Root (Construction Maybe) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

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

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Substructure ('Root :: a -> Segment a) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

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

Substructure ('Tail :: a -> Segment a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Substructural 'Tail (Construction Maybe) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substructural 'Tail (Construction List) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substructural 'Root (Construction List) :: Type -> Type Source #

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 Nonempty Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Zipper List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Combinative 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 Schematic Monad Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

type Measural 'Length List a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Measural 'Heighth Binary a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Measural 'Length (Construction Maybe) a Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Zipper (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Zipper (Comprehension 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.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 (Construction Maybe)) (Vector r) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

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

Defined in Pandora.Paradigm.Primary

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

Defined in Pandora.Paradigm.Structure.Some.List

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 List) (Vector r) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Linear.Vector

type Morphing ('Into List) (Vector r) = 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 ((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 ('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.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 ('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 (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 ('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 ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction List) k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Morphing ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed (Construction List) k) = ((Product (Nonempty List k) <:.> Identity) <:.:> Prefixed (Construction List) k) := ((->) :: Type -> Type -> Type)
type Morphing ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Morphing ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Rose k) = ((Product (Nonempty List k) <:.> Identity) <:.:> Prefixed Rose k) := ((->) :: Type -> Type -> Type)
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 ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Vary ('Element :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) = ((Product k <:.> Identity) <:.:> Prefixed Binary k) := ((->) :: Type -> Type -> Type)
type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

type Morphing ('Lookup ('Key :: a -> Morph a) :: Morph (a -> Morph a)) (Prefixed Binary k) = ((->) k :: Type -> Type) <:.> Maybe
type Morphing ('Into ('Here Maybe :: Wedge (Type -> Type) a1) :: Morph (Wedge (Type -> Type) a1)) (Flip Wedge a2) Source # 
Instance details

Defined in Pandora.Paradigm.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 Substructural ('Tail :: a -> Segment a) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

type Substructural ('Root :: a -> Segment a) List = Maybe
type Substructural ('Just :: a -> Maybe a) Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substructural ('Root :: a -> Segment a) Rose Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substructural ('Root :: a -> Segment a) Rose = Maybe
type Substructural ('Right :: a -> Wye a) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

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

Defined in Pandora.Paradigm.Structure.Some.Binary

type Substructural ('Left :: a -> Wye a) Binary = Binary
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 Substructural ('Right :: a -> Wye a) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

type Substructural ('Root :: a -> Segment a) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substructural ('Root :: a -> Segment a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

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

Defined in Pandora.Paradigm.Structure.Some.List

type Substructural ('Left :: a -> Wye a) (Tap ((List <:.:> List) := (:*:))) = List
type Substructural ('Root :: a -> Segment a) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substructural ('Tail :: a -> Segment a) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Substructural ('Tail :: a -> Segment a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substructural ('Root :: a -> Segment a) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

nothing :: Optional t => t a Source #