Safe Haskell | None |
---|---|
Language | Haskell2010 |
Definitions of strict linked list.
Most basic operations like fmap
, filter
, <*>
can only be implemented efficiently by producing an intermediate list in reversed order
and then reversing it to the original order.
These intermediate reversed functions are exposed by the API,
because they very well may be useful for efficient implementations of data-structures built on top of list.
E.g., the "deque" package exploits them heavily.
One useful rule of thumb would be that whenever you see that a function has a reversed counterpart, that counterpart is faster and hence if you don't care about the order or intend to reverse the list further down the line, you should give preference to that counterpart.
The typical toList
and fromList
conversions are provided by means of
the Foldable
and IsList
instances.
Synopsis
- data List a
- reverse :: List a -> List a
- take :: Int -> List a -> List a
- takeReversed :: Int -> List a -> List a
- drop :: Int -> List a -> List a
- filter :: (a -> Bool) -> List a -> List a
- filterReversed :: (a -> Bool) -> List a -> List a
- takeWhile :: (a -> Bool) -> List a -> List a
- takeWhileReversed :: (a -> Bool) -> List a -> List a
- dropWhile :: (a -> Bool) -> List a -> List a
- span :: (a -> Bool) -> List a -> (List a, List a)
- spanReversed :: (a -> Bool) -> List a -> (List a, List a)
- break :: (a -> Bool) -> List a -> (List a, List a)
- breakReversed :: (a -> Bool) -> List a -> (List a, List a)
- takeWhileFromEnding :: (a -> Bool) -> List a -> List a
- dropWhileFromEnding :: (a -> Bool) -> List a -> List a
- spanFromEnding :: (a -> Bool) -> List a -> (List a, List a)
- uncons :: List a -> Maybe (a, List a)
- head :: List a -> Maybe a
- last :: List a -> Maybe a
- tail :: List a -> List a
- init :: List a -> List a
- initReversed :: List a -> List a
- apZipping :: List (a -> b) -> List a -> List b
- apZippingReversed :: List (a -> b) -> List a -> List b
- fromListReversed :: [a] -> List a
- prependReversed :: List a -> List a -> List a
- mapReversed :: (a -> b) -> List a -> List b
- apReversed :: List (a -> b) -> List a -> List b
- explodeReversed :: (a -> List b) -> List a -> List b
- joinReversed :: List (List a) -> List a
Documentation
Strict linked list.
Instances
Monad List Source # | |
Functor List Source # | |
Applicative List Source # | |
Foldable List Source # | |
Defined in StrictList fold :: Monoid m => List m -> m # foldMap :: Monoid m => (a -> m) -> List a -> m # foldr :: (a -> b -> b) -> b -> List a -> b # foldr' :: (a -> b -> b) -> b -> List a -> b # foldl :: (b -> a -> b) -> b -> List a -> b # foldl' :: (b -> a -> b) -> b -> List a -> b # foldr1 :: (a -> a -> a) -> List a -> a # foldl1 :: (a -> a -> a) -> List a -> a # elem :: Eq a => a -> List a -> Bool # maximum :: Ord a => List a -> a # | |
Traversable List Source # | |
Alternative List Source # | |
MonadPlus List Source # | |
Plus List Source # | |
Defined in StrictList | |
Alt List Source # | |
Apply List Source # | |
Bind List Source # | |
IsList (List a) Source # | |
Eq a => Eq (List a) Source # | |
Data a => Data (List a) Source # | |
Defined in StrictList gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> List a -> c (List a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (List a) # toConstr :: List a -> Constr # dataTypeOf :: List a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (List a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (List a)) # gmapT :: (forall b. Data b => b -> b) -> List a -> List a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> List a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> List a -> r # gmapQ :: (forall d. Data d => d -> u) -> List a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> List a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> List a -> m (List a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> List a -> m (List a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> List a -> m (List a) # | |
Ord a => Ord (List a) Source # | |
Read a => Read (List a) Source # | |
Show a => Show (List a) Source # | |
Generic (List a) Source # | |
Semigroup (List a) Source # | |
Monoid (List a) Source # | |
Generic1 List Source # | |
type Rep (List a) Source # | |
Defined in StrictList type Rep (List a) = D1 (MetaData "List" "StrictList" "strict-list-0.1.4-8OXWdUL45U2HCgqq9RTMla" False) (C1 (MetaCons "Cons" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (List a))) :+: C1 (MetaCons "Nil" PrefixI False) (U1 :: Type -> Type)) | |
type Item (List a) Source # | |
Defined in StrictList | |
type Rep1 List Source # | |
Defined in StrictList type Rep1 List = D1 (MetaData "List" "StrictList" "strict-list-0.1.4-8OXWdUL45U2HCgqq9RTMla" False) (C1 (MetaCons "Cons" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1 :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec1 List)) :+: C1 (MetaCons "Nil" PrefixI False) (U1 :: Type -> Type)) |
takeReversed :: Int -> List a -> List a Source #
Leave only the specified amount of elements, in reverse order.
drop :: Int -> List a -> List a Source #
Leave only the elements after the specified amount of first elements.
filterReversed :: (a -> Bool) -> List a -> List a Source #
Leave only the elements satisfying the predicate, producing a list in reversed order.
takeWhile :: (a -> Bool) -> List a -> List a Source #
Leave only the first elements satisfying the predicate.
takeWhileReversed :: (a -> Bool) -> List a -> List a Source #
Leave only the first elements satisfying the predicate, producing a list in reversed order.
dropWhile :: (a -> Bool) -> List a -> List a Source #
Drop the first elements satisfying the predicate.
spanReversed :: (a -> Bool) -> List a -> (List a, List a) Source #
Same as span
, only with the first list in reverse order.
break :: (a -> Bool) -> List a -> (List a, List a) Source #
An opposite version of span
. I.e.,
break predicate = span (not . predicate)
breakReversed :: (a -> Bool) -> List a -> (List a, List a) Source #
Same as break
, only with the first list in reverse order.
uncons :: List a -> Maybe (a, List a) Source #
Get the first element and the remainder of the list if it's not empty.
initReversed :: List a -> List a Source #
Get all elements but the last one, producing the results in reverse order.
apZipping :: List (a -> b) -> List a -> List b Source #
Apply the functions in the left list to elements in the right one.
apZippingReversed :: List (a -> b) -> List a -> List b Source #
Apply the functions in the left list to elements in the right one, producing a list of results in reversed order.
Reversed intermediate functions used in instances
fromListReversed :: [a] -> List a Source #
Construct from a lazy list in reversed order.
prependReversed :: List a -> List a -> List a Source #
Add elements of the left list in reverse order in the beginning of the right list.
mapReversed :: (a -> b) -> List a -> List b Source #
Map producing a list in reversed order.
apReversed :: List (a -> b) -> List a -> List b Source #
Apply the functions in the left list to every element in the right one, producing a list of results in reversed order.