pandora-0.5.1: 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 list

Orphan instances

Zippable List Source # 
Instance details

Associated Types

type Breadcrumbs List :: Type -> Type Source #

Stack List Source # 
Instance details

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 #

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 #

Zippable (Construction Maybe) Source # 
Instance details

Associated Types

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

Zippable (Comprehension Maybe) Source # 
Instance details

Associated Types

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

Stack (Construction Maybe) Source # 
Instance details

Associated Types

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

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

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

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

Associated Types

type Morphing ('Into (Tape 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 (Construction Maybe)) (Tape (Construction Maybe)) Source # 
Instance details

Associated Types

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

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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

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

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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

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

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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

Semigroup (Construction Maybe a) Source # 
Instance details

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

Methods

(<<=) :: (Tape List a -> b) -> Tape List a -> Tape List b Source #

(<<==) :: (Tape List a -> b) -> Tape List a -> Tape List b Source #

(<<===) :: (Tape List a -> b) -> Tape List a -> Tape List b Source #

(<<====) :: (Tape List a -> b) -> Tape List a -> Tape List b Source #

(<<=====) :: (Tape List a -> b) -> Tape List a -> Tape List b Source #

(<<======) :: (Tape List a -> b) -> Tape List a -> Tape List b Source #

(<<=======) :: (Tape List a -> b) -> Tape List a -> Tape List b Source #

(<<========) :: (Tape List a -> b) -> Tape List a -> Tape List b Source #

(<<=========) :: (Tape List a -> b) -> Tape List a -> Tape List b Source #

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 Available 'Tail List :: Type -> Type Source #

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

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

Associated Types

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

type Substance 'Root 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 ('Root :: a -> Segment a) (Construction Maybe) Source # 
Instance details

Associated Types

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

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

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

Associated Types

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

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

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

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 #

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