ralist-0.4.0.0: Random access list with a list compatible interface.
Safe HaskellTrustworthy
LanguageHaskell2010

Data.RAList

Description

A random-access list implementation based on Chris Okasaki's approach on his book "Purely Functional Data Structures", Cambridge University Press, 1998, chapter 9.3.

RAList is a replacement for ordinary finite lists. RAList provides the same complexity as ordinary for most the list operations. Some operations take O(log n) for RAList where the list operation is O(n), notably indexing, (!!).

Synopsis

Documentation

data RAList a where Source #

Bundled Patterns

pattern Nil :: forall a. RAList a

our '[]' by another name

pattern Cons :: forall a. a -> RAList a -> RAList a infixr 5

Constructor notation :

pattern (:|) :: forall a. a -> RAList a -> RAList a infixr 5

like : but for RAList

Instances

Instances details
Monad RAList Source # 
Instance details

Defined in Data.RAList

Methods

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

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

return :: a -> RAList a #

Functor RAList Source # 
Instance details

Defined in Data.RAList

Methods

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

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

Applicative RAList Source # 
Instance details

Defined in Data.RAList

Methods

pure :: a -> RAList a #

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

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

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

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

Foldable RAList Source # 
Instance details

Defined in Data.RAList

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> RAList a -> m #

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

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

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

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

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

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

toList :: RAList a -> [a] #

null :: RAList a -> Bool #

length :: RAList a -> Int #

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

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

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

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

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

Traversable RAList Source # 
Instance details

Defined in Data.RAList

Methods

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

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

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

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

MonadZip RAList Source # 
Instance details

Defined in Data.RAList

Methods

mzip :: RAList a -> RAList b -> RAList (a, b) #

mzipWith :: (a -> b -> c) -> RAList a -> RAList b -> RAList c #

munzip :: RAList (a, b) -> (RAList a, RAList b) #

NFData1 RAList Source # 
Instance details

Defined in Data.RAList

Methods

liftRnf :: (a -> ()) -> RAList a -> () #

FunctorWithIndex Word64 RAList Source # 
Instance details

Defined in Data.RAList

Methods

imap :: (Word64 -> a -> b) -> RAList a -> RAList b #

FoldableWithIndex Word64 RAList Source # 
Instance details

Defined in Data.RAList

Methods

ifoldMap :: Monoid m => (Word64 -> a -> m) -> RAList a -> m #

ifoldMap' :: Monoid m => (Word64 -> a -> m) -> RAList a -> m #

ifoldr :: (Word64 -> a -> b -> b) -> b -> RAList a -> b #

ifoldl :: (Word64 -> b -> a -> b) -> b -> RAList a -> b #

ifoldr' :: (Word64 -> a -> b -> b) -> b -> RAList a -> b #

ifoldl' :: (Word64 -> b -> a -> b) -> b -> RAList a -> b #

TraversableWithIndex Word64 RAList Source # 
Instance details

Defined in Data.RAList

Methods

itraverse :: Applicative f => (Word64 -> a -> f b) -> RAList a -> f (RAList b) #

IsList (RAList a) Source # 
Instance details

Defined in Data.RAList

Associated Types

type Item (RAList a) #

Methods

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

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

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

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

Defined in Data.RAList

Methods

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

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

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

Defined in Data.RAList

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RAList a -> c (RAList a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RAList a) #

toConstr :: RAList a -> Constr #

dataTypeOf :: RAList a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RAList a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RAList a)) #

gmapT :: (forall b. Data b => b -> b) -> RAList a -> RAList a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RAList a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RAList a -> r #

gmapQ :: (forall d. Data d => d -> u) -> RAList a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RAList a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RAList a -> m (RAList a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RAList a -> m (RAList a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RAList a -> m (RAList a) #

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

Defined in Data.RAList

Methods

compare :: RAList a -> RAList a -> Ordering #

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

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

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

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

max :: RAList a -> RAList a -> RAList a #

min :: RAList a -> RAList a -> RAList a #

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

Defined in Data.RAList

Methods

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

show :: RAList a -> String #

showList :: [RAList a] -> ShowS #

Generic (RAList a) Source # 
Instance details

Defined in Data.RAList

Associated Types

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

Methods

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

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

Semigroup (RAList a) Source # 
Instance details

Defined in Data.RAList

Methods

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

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

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

Monoid (RAList a) Source # 
Instance details

Defined in Data.RAList

Methods

mempty :: RAList a #

mappend :: RAList a -> RAList a -> RAList a #

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

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

Defined in Data.RAList

Methods

rnf :: RAList a -> () #

Generic1 RAList Source # 
Instance details

Defined in Data.RAList

Associated Types

type Rep1 RAList :: k -> Type #

Methods

from1 :: forall (a :: k). RAList a -> Rep1 RAList a #

to1 :: forall (a :: k). Rep1 RAList a -> RAList a #

type Rep (RAList a) Source # 
Instance details

Defined in Data.RAList

type Rep (RAList a)
type Item (RAList a) Source # 
Instance details

Defined in Data.RAList

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

Defined in Data.RAList

Basic functions

cons :: a -> RAList a -> RAList a infixr 5 Source #

Complexity O(1).

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

(++) :: RAList a -> RAList a -> RAList a infixr 5 Source #

head :: RAList a -> Maybe a Source #

Complexity O(1).

last :: RAList a -> a Source #

Complexity O(log n).

tail :: RAList a -> Maybe (RAList a) Source #

Complexity O(1).

null :: Foldable t => t a -> Bool #

Test whether the structure is empty. The default implementation is optimized for structures that are similar to cons-lists, because there is no general way to do better.

Since: base-4.8.0.0

length :: Foldable t => t a -> Int #

Returns the size/length of a finite structure as an Int. The default implementation is optimized for structures that are similar to cons-lists, because there is no general way to do better.

Since: base-4.8.0.0

Indexing lists

These functions treat a list xs as a indexed collection, with indices ranging from 0 to length xs - 1.

(!!) :: RAList a -> Word64 -> a infixl 9 Source #

Complexity O(log n).

lookupWithDefault :: forall t. t -> Word64 -> RAList t -> t Source #

lookupM :: forall a m. MonadFail m => RAList a -> Word64 -> m a Source #

lookup :: forall a. RAList a -> Word64 -> Maybe a Source #

lookupCC :: forall a r. RAList a -> Word64 -> (a -> r) -> (String -> r) -> r Source #

lookupL :: Eq a => a -> RAList (a, b) -> Maybe b Source #

List transformations

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

reverse :: RAList a -> RAList a Source #

reverse xs returns the elements of xs in reverse order. xs must be finite.

indexed operations

imap :: FunctorWithIndex i f => (i -> a -> b) -> f a -> f b #

Map with access to the index.

itraverse :: (TraversableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f (t b) #

Traverse an indexed container.

itraverseitraverseOf itraversed

ifoldMap :: (FoldableWithIndex i f, Monoid m) => (i -> a -> m) -> f a -> m #

Fold a container by mapping value to an arbitrary Monoid with access to the index i.

When you don't need access to the index then foldMap is more flexible in what it accepts.

foldMapifoldMap . const

ifoldl' :: FoldableWithIndex i f => (i -> b -> a -> b) -> b -> f a -> b #

Fold over the elements of a structure with an index, associating to the left, but strictly.

When you don't need access to the index then foldlOf' is more flexible in what it accepts.

foldlOf' l ≡ ifoldlOf' l . const

ifoldr :: FoldableWithIndex i f => (i -> a -> b -> b) -> b -> f a -> b #

Right-associative fold of an indexed container with access to the index i.

When you don't need access to the index then foldr is more flexible in what it accepts.

foldrifoldr . const

Reducing lists (folds)

foldl :: Foldable t => (b -> a -> b) -> b -> t a -> b #

Left-associative fold of a structure.

In the case of lists, foldl, when applied to a binary operator, a starting value (typically the left-identity of the operator), and a list, reduces the list using the binary operator, from left to right:

foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn

Note that to produce the outermost application of the operator the entire input list must be traversed. This means that foldl' will diverge if given an infinite list.

Also note that if you want an efficient left-fold, you probably want to use foldl' instead of foldl. The reason for this is that latter does not force the "inner" results (e.g. z `f` x1 in the above example) before applying them to the operator (e.g. to (`f` x2)). This results in a thunk chain \(\mathcal{O}(n)\) elements long, which then must be evaluated from the outside-in.

For a general Foldable structure this should be semantically identical to,

foldl f z = foldl f z . toList

foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b #

Left-associative fold of a structure but with strict application of the operator.

This ensures that each step of the fold is forced to weak head normal form before being applied, avoiding the collection of thunks that would otherwise occur. This is often what you want to strictly reduce a finite list to a single, monolithic result (e.g. length).

For a general Foldable structure this should be semantically identical to,

foldl' f z = foldl' f z . toList

Since: base-4.6.0.0

foldl1 :: Foldable t => (a -> a -> a) -> t a -> a #

A variant of foldl that has no base case, and thus may only be applied to non-empty structures.

foldl1 f = foldl1 f . toList

foldl1' :: (a -> a -> a) -> RAList a -> a Source #

foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b #

Right-associative fold of a structure.

In the case of lists, foldr, when applied to a binary operator, a starting value (typically the right-identity of the operator), and a list, reduces the list using the binary operator, from right to left:

foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)

Note that, since the head of the resulting expression is produced by an application of the operator to the first element of the list, foldr can produce a terminating expression from an infinite list.

For a general Foldable structure this should be semantically identical to,

foldr f z = foldr f z . toList

foldr1 :: Foldable t => (a -> a -> a) -> t a -> a #

A variant of foldr that has no base case, and thus may only be applied to non-empty structures.

foldr1 f = foldr1 f . toList

Special folds

concatMap :: (a -> RAList b) -> RAList a -> RAList b Source #

and :: Foldable t => t Bool -> Bool #

and returns the conjunction of a container of Bools. For the result to be True, the container must be finite; False, however, results from a False value finitely far from the left end.

or :: Foldable t => t Bool -> Bool #

or returns the disjunction of a container of Bools. For the result to be False, the container must be finite; True, however, results from a True value finitely far from the left end.

any :: Foldable t => (a -> Bool) -> t a -> Bool #

Determines whether any element of the structure satisfies the predicate.

all :: Foldable t => (a -> Bool) -> t a -> Bool #

Determines whether all elements of the structure satisfy the predicate.

sum :: (Foldable t, Num a) => t a -> a #

The sum function computes the sum of the numbers of a structure.

Since: base-4.8.0.0

product :: (Foldable t, Num a) => t a -> a #

The product function computes the product of the numbers of a structure.

Since: base-4.8.0.0

maximum :: (Foldable t, Ord a) => t a -> a #

The largest element of a non-empty structure.

Since: base-4.8.0.0

minimum :: (Foldable t, Ord a) => t a -> a #

The least element of a non-empty structure.

Since: base-4.8.0.0

Building lists

Repetition

Unfolding

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

Sublists

Extracting sublists

drop :: Word64 -> RAList a -> RAList a Source #

drop i l where l has length n has worst case complexity Complexity O(log n), Average case complexity should be O(min(log i, log n)).

Searching lists

Searching by equality

elem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 #

Does the element occur in the structure?

Since: base-4.8.0.0

notElem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 #

notElem is the negation of elem.

filter :: forall a. (a -> Bool) -> RAList a -> RAList a Source #

partition :: (a -> Bool) -> RAList a -> (RAList a, RAList a) Source #

mapMaybe :: forall a b. (a -> Maybe b) -> RAList a -> RAList b Source #

wither :: forall a b f. Applicative f => (a -> f (Maybe b)) -> RAList a -> f (RAList b) Source #

Zipping and unzipping lists

zip :: RAList a -> RAList b -> RAList (a, b) Source #

zipWith :: forall a b c. (a -> b -> c) -> RAList a -> RAList b -> RAList c Source #

unzip :: RAList (a, b) -> (RAList a, RAList b) Source #

The "generic" operations

The prefix `generic' indicates an overloaded function that is a generalized version of a Prelude function.

genericIndex :: Integral n => RAList a -> n -> a Source #

Update

update :: Word64 -> a -> RAList a -> RAList a Source #

Change element at the given index. Complexity O(log n).

adjust :: forall a. (a -> a) -> Word64 -> RAList a -> RAList a Source #

Apply a function to the value at the given index. Complexity O(log n).

List conversion

toList :: Foldable t => t a -> [a] #

List of elements of a structure, from left to right.

Since: base-4.8.0.0

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

Complexity O(n).

List style fusion tools

build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> RAList a Source #

augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> RAList a -> RAList a Source #