dlist-1.0: Difference lists

Copyright© 2006-2009 Don Stewart 2013-2020 Sean Leather
LicenseBSD-3-Clause
Maintainersean.leather@gmail.com
Stabilitystable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.DList

Contents

Description

A difference list is an abstraction representing a list that supports \(\mathcal{O}\)(1) append and snoc operations. This module provides the type for a difference list, DList, and a collection of supporting functions for (a) converting to and from lists and (b) operating on DLists efficiently.

Synopsis

Difference List Type

data DList a where Source #

A difference list is an abstraction representing a list that supports \(\mathcal{O}\)(1) append and snoc operations, making it useful for replacing frequent applications of ++ such as logging and pretty printing (esp. if those uses of ++ are left-nested).

Bundled Patterns

pattern Nil :: DList a

A unidirectional pattern synonym for empty. This is implemented with toList.

pattern Cons :: a -> [a] -> DList a

A unidirectional pattern synonym for cons. This is implemented with toList.

Instances
Monad DList Source # 
Instance details

Defined in Data.DList.Internal

Methods

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

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

return :: a -> DList a #

fail :: String -> DList a #

Functor DList Source # 
Instance details

Defined in Data.DList.Internal

Methods

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

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

MonadFail DList Source # 
Instance details

Defined in Data.DList.Internal

Methods

fail :: String -> DList a #

Applicative DList Source # 
Instance details

Defined in Data.DList.Internal

Methods

pure :: a -> DList a #

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

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

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

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

Foldable DList Source # 
Instance details

Defined in Data.DList.Internal

Methods

fold :: Monoid m => DList m -> m #

foldMap :: Monoid m => (a -> m) -> DList a -> m #

foldr :: (a -> b -> b) -> b -> DList a -> b #

foldr' :: (a -> b -> b) -> b -> DList a -> b #

foldl :: (b -> a -> b) -> b -> DList a -> b #

foldl' :: (b -> a -> b) -> b -> DList a -> b #

foldr1 :: (a -> a -> a) -> DList a -> a #

foldl1 :: (a -> a -> a) -> DList a -> a #

toList :: DList a -> [a] #

null :: DList a -> Bool #

length :: DList a -> Int #

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

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

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

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

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

Traversable DList Source # 
Instance details

Defined in Data.DList.Internal

Methods

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

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

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

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

Alternative DList Source # 
Instance details

Defined in Data.DList.Internal

Methods

empty :: DList a #

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

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

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

MonadPlus DList Source # 
Instance details

Defined in Data.DList.Internal

Methods

mzero :: DList a #

mplus :: DList a -> DList a -> DList a #

IsList (DList a) Source # 
Instance details

Defined in Data.DList.Internal

Associated Types

type Item (DList a) :: Type #

Methods

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

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

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

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

Defined in Data.DList.Internal

Methods

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

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

Ord a => Ord (DList a) Source # 
Instance details

Defined in Data.DList.Internal

Methods

compare :: DList a -> DList a -> Ordering #

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

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

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

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

max :: DList a -> DList a -> DList a #

min :: DList a -> DList a -> DList a #

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

Defined in Data.DList.Internal

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

Defined in Data.DList.Internal

Methods

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

show :: DList a -> String #

showList :: [DList a] -> ShowS #

a ~ Char => IsString (DList a) Source # 
Instance details

Defined in Data.DList.Internal

Methods

fromString :: String -> DList a #

Semigroup (DList a) Source # 
Instance details

Defined in Data.DList.Internal

Methods

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

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

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

Monoid (DList a) Source # 
Instance details

Defined in Data.DList.Internal

Methods

mempty :: DList a #

mappend :: DList a -> DList a -> DList a #

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

NFData a => NFData (DList a) Source # 
Instance details

Defined in Data.DList.Internal

Methods

rnf :: DList a -> () #

type Item (DList a) Source # 
Instance details

Defined in Data.DList.Internal

type Item (DList a) = a

Conversion

fromList :: [a] -> DList a Source #

fromList xs is a DList representing the list xs.

fromList obeys the laws:

toList . fromList = id
fromList . toList = id

This function is implemented with ++. Repeated uses of fromList are just as inefficient as repeated uses of ++. If you find yourself doing some form of the following (possibly indirectly), you may not be taking advantage of the DList representation and library:

fromList . f . toList

More likely, you will convert from a list, perform some operation on the DList, and convert back to a list:

toList . g . fromList

toList :: DList a -> [a] Source #

toList xs is the list represented by xs.

toList obeys the laws:

toList . fromList = id
fromList . toList = id

Evaluating toList xs may “collapse” the chain of function composition underlying many DList functions (append in particular) used to construct xs. This may affect any efficiency you achieved due to laziness in the construction.

apply :: DList a -> [a] -> [a] Source #

apply xs ys is the list represented by the xs after appending ys to it.

\(\mathcal{O}\)(1).

apply obeys the law:

apply xs ys = toList xs ++ ys

Basic Functions

empty :: DList a Source #

empty is a DList with no elements.

empty obeys the law:

toList empty = []

singleton :: a -> DList a Source #

singleton x is a DList with the single element x.

singleton obeys the law:

toList (singleton x) = [x]

cons :: a -> DList a -> DList a infixr 9 Source #

cons x xs is a DList with the head x and the tail xs.

\(\mathcal{O}\)(1).

cons obeys the law:

toList (cons x xs) = x : toList xs

snoc :: DList a -> a -> DList a infixl 9 Source #

snoc xs x is a DList with the initial DList xs and the last element x.

\(\mathcal{O}\)(1).

snoc obeys the law:

toList (snoc xs x) = toList xs ++ [x]

append :: DList a -> DList a -> DList a Source #

append xs ys is a DList obtained from the concatenation of the elements of xs and ys.

\(\mathcal{O}\)(1).

append obeys the law:

toList (append xs ys) = toList xs ++ toList ys

concat :: [DList a] -> DList a Source #

concat xss is a DList representing the concatenation of all DLists in the list xss.

\(\mathcal{O}\)(length xss).

concat obeys the law:

toList (concat xss) = concat (map toList xss)

replicate :: Int -> a -> DList a Source #

replicate n x is a DList of length n with x as the value of every element.

\(\mathcal{O}\)(n).

replicate obeys the law:

toList (replicate n x) = replicate n x

head :: DList a -> a Source #

head xs is the first element of xs. If xs is empty, an error is raised.

\(\mathcal{O}\)(1).

head obeys the law:

head xs = head (toList xs)

tail :: DList a -> [a] Source #

tail xs is a list of the elements in xs excluding the first element. If xs is empty, an error is raised.

\(\mathcal{O}\)(length (toList xs)).

tail obeys the law:

tail xs = tail (toList xs)

unfoldr :: (b -> Maybe (a, b)) -> b -> DList a Source #

unfoldr f z is the DList constructed from the recursive application of f. The recursion starts with the seed value z and ends when, for some z' : b, f z' == Nothing.

\(\mathcal{O}\)(length (unfoldr f z)).

unfoldr obeys the law:

toList (unfoldr f z) = unfoldr f z

foldr :: (a -> b -> b) -> b -> DList a -> b Source #

foldr f z xs is the right-fold of f over xs.

\(\mathcal{O}\)(length (toList xs)).

foldr obeys the law:

foldr f z xs = foldr f z (toList xs)

map :: (a -> b) -> DList a -> DList b Source #

map f xs is the DList obtained by applying f to each element of xs.

\(\mathcal{O}\)(length (toList xs)).

map obeys the law:

toList (map f xs) = map f (toList xs)

intercalate :: DList a -> [DList a] -> DList a Source #

intercalate xs xss is the concatenation of xss after the insertion of xs between every pair of elements.

\(\mathcal{O}\)(length xss).

intercalate obeys the law:

toList (intercalate xs xss) = intercalate (toList xs) (map toList xss)