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

Pandora.Paradigm.Structure.Some.List

Synopsis

Documentation

type List = Maybe <:.> Construction Maybe Source #

Linear data structure that serves as a collection of elements

linearize :: forall t a. Traversable t => t a -> List a Source #

Transform any traversable structure into a stack

Orphan instances

Stack List Source # 
Instance details

Measurable 'Length List Source # 
Instance details

Associated Types

type Measural 'Length List a Source #

Measurable 'Length (Construction Maybe) Source # 
Instance details

Associated Types

type Measural 'Length (Construction Maybe) a Source #

Monotonic a (Construction Maybe a) Source # 
Instance details

Methods

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

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

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

Methods

reduce :: (a -> r -> r) -> r -> ((Maybe <:.> Construction Maybe) := a) -> r Source #

resolve :: (a -> r) -> r -> ((Maybe <:.> Construction Maybe) := a) -> r Source #

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

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

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

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

Methods

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

Monoid (List a) Source # 
Instance details

Methods

zero :: List a Source #

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

Methods

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

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

Nullable List Source # 
Instance details

Methods

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

Focusable ('Head :: Type -> Location Type) List Source # 
Instance details

Associated Types

type Focusing 'Head List a Source #

Focusable ('Head :: Type -> Location Type) (Tap ((Construction Maybe <:.:> Construction Maybe) := (:*:))) Source # 
Instance details

Focusable ('Head :: Type -> Location Type) (Tap ((List <:.:> List) := (:*:))) Source # 
Instance details

Associated Types

type Focusing 'Head (Tap ((List <:.:> List) := (:*:))) a Source #

Focusable ('Head :: Type -> Location Type) (Construction Maybe) Source # 
Instance details

Associated Types

type Focusing 'Head (Construction Maybe) a Source #

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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

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

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

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

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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

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

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

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

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

Associated Types

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

Semigroup (Construction Maybe a) Source # 
Instance details

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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