strict-list-0.1.2: Strict linked list

Safe HaskellNone
LanguageHaskell2010

StrictList

Contents

Description

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

Documentation

data List a Source #

Strict linked list.

Constructors

Cons !a !(List a) 
Nil 
Instances
Monad List Source # 
Instance details

Defined in StrictList

Methods

(>>=) :: List a -> (a -> List b) -> List b #

(>>) :: List a -> List b -> List b #

return :: a -> List a #

fail :: String -> List a #

Functor List Source # 
Instance details

Defined in StrictList

Methods

fmap :: (a -> b) -> List a -> List b #

(<$) :: a -> List b -> List a #

Applicative List Source # 
Instance details

Defined in StrictList

Methods

pure :: a -> List a #

(<*>) :: List (a -> b) -> List a -> List b #

liftA2 :: (a -> b -> c) -> List a -> List b -> List c #

(*>) :: List a -> List b -> List b #

(<*) :: List a -> List b -> List a #

Foldable List Source # 
Instance details

Defined in StrictList

Methods

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 #

toList :: List a -> [a] #

null :: List a -> Bool #

length :: List a -> Int #

elem :: Eq a => a -> List a -> Bool #

maximum :: Ord a => List a -> a #

minimum :: Ord a => List a -> a #

sum :: Num a => List a -> a #

product :: Num a => List a -> a #

Traversable List Source # 
Instance details

Defined in StrictList

Methods

traverse :: Applicative f => (a -> f b) -> List a -> f (List b) #

sequenceA :: Applicative f => List (f a) -> f (List a) #

mapM :: Monad m => (a -> m b) -> List a -> m (List b) #

sequence :: Monad m => List (m a) -> m (List a) #

Alternative List Source # 
Instance details

Defined in StrictList

Methods

empty :: List a #

(<|>) :: List a -> List a -> List a #

some :: List a -> List [a] #

many :: List a -> List [a] #

MonadPlus List Source # 
Instance details

Defined in StrictList

Methods

mzero :: List a #

mplus :: List a -> List a -> List a #

Plus List Source # 
Instance details

Defined in StrictList

Methods

zero :: List a #

Alt List Source # 
Instance details

Defined in StrictList

Methods

(<!>) :: List a -> List a -> List a #

some :: Applicative List => List a -> List [a] #

many :: Applicative List => List a -> List [a] #

Apply List Source # 
Instance details

Defined in StrictList

Methods

(<.>) :: List (a -> b) -> List a -> List b #

(.>) :: List a -> List b -> List b #

(<.) :: List a -> List b -> List a #

liftF2 :: (a -> b -> c) -> List a -> List b -> List c #

Bind List Source # 
Instance details

Defined in StrictList

Methods

(>>-) :: List a -> (a -> List b) -> List b #

join :: List (List a) -> List a #

IsList (List a) Source # 
Instance details

Defined in StrictList

Associated Types

type Item (List a) :: Type #

Methods

fromList :: [Item (List a)] -> List a #

fromListN :: Int -> [Item (List a)] -> List a #

toList :: List a -> [Item (List a)] #

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

Defined in StrictList

Methods

(==) :: List a -> List a -> Bool #

(/=) :: List a -> List a -> Bool #

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

Defined in StrictList

Methods

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 # 
Instance details

Defined in StrictList

Methods

compare :: List a -> List a -> Ordering #

(<) :: List a -> List a -> Bool #

(<=) :: List a -> List a -> Bool #

(>) :: List a -> List a -> Bool #

(>=) :: List a -> List a -> Bool #

max :: List a -> List a -> List a #

min :: List a -> List a -> List a #

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

Defined in StrictList

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

Defined in StrictList

Methods

showsPrec :: Int -> List a -> ShowS #

show :: List a -> String #

showList :: [List a] -> ShowS #

Generic (List a) Source # 
Instance details

Defined in StrictList

Associated Types

type Rep (List a) :: Type -> Type #

Methods

from :: List a -> Rep (List a) x #

to :: Rep (List a) x -> List a #

Semigroup (List a) Source # 
Instance details

Defined in StrictList

Methods

(<>) :: List a -> List a -> List a #

sconcat :: NonEmpty (List a) -> List a #

stimes :: Integral b => b -> List a -> List a #

Monoid (List a) Source # 
Instance details

Defined in StrictList

Methods

mempty :: List a #

mappend :: List a -> List a -> List a #

mconcat :: [List a] -> List a #

Generic1 List Source # 
Instance details

Defined in StrictList

Associated Types

type Rep1 List :: k -> Type #

Methods

from1 :: List a -> Rep1 List a #

to1 :: Rep1 List a -> List a #

type Rep (List a) Source # 
Instance details

Defined in StrictList

type Rep (List a) = D1 (MetaData "List" "StrictList" "strict-list-0.1.2-IV3Lc4vmVbZHeKbIE6MRNj" 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 # 
Instance details

Defined in StrictList

type Item (List a) = a
type Rep1 List Source # 
Instance details

Defined in StrictList

reverse :: List a -> List a Source #

Reverse the list.

take :: Int -> List a -> List a Source #

Leave only the specified amount of elements.

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.

filter :: (a -> Bool) -> List a -> List a Source #

Leave only the elements satisfying the predicate.

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.

span :: (a -> Bool) -> List a -> (List a, List a) Source #

An optimized version of the same predicate applied to takeWhile and dropWhile. IOW,

span predicate list = (takeWhile predicate list, dropWhile predicate list)

spanReversed :: (a -> Bool) -> List a -> (List a, List a) Source #

Same as span, only with the first list in reverse order.

takeWhileFromEnding :: (a -> Bool) -> List a -> List a Source #

Same as (takeWhile predicate . reverse). E.g.,

>>> takeWhileFromEnding (> 2) (fromList [1,4,2,3,4,5])
fromList [5,4,3]

dropWhileFromEnding :: (a -> Bool) -> List a -> List a Source #

Same as (dropWhile predicate . reverse). E.g.,

>>> dropWhileFromEnding (> 2) (fromList [1,4,2,3,4,5])
fromList [2,4,1]

uncons :: List a -> Maybe (a, List a) Source #

Get the first element and the remainder of the list if it's not empty.

head :: List a -> Maybe a Source #

Get the first element, if list is not empty.

last :: List a -> Maybe a Source #

Get the last element, if list is not empty.

tail :: List a -> List a Source #

Get all elements of the list but the first one.

init :: List a -> List a Source #

Get all elements but the last one.

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.

explodeReversed :: (a -> List b) -> List a -> List b Source #

Use a function to produce a list of lists and then concat them sequentially, producing the results in reversed order.

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

Join (concat) producing results in reversed order.