ralist-0.2.0.0: Random access list with a list compatible interface.

Safe HaskellSafe
LanguageHaskell2010

Data.RAList

Contents

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 Source #

Instances

Monad RAList Source # 

Methods

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

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

return :: a -> RAList a #

fail :: String -> RAList a #

Functor RAList Source # 

Methods

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

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

Applicative RAList Source # 

Methods

pure :: a -> RAList a #

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

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

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

Foldable RAList Source # 

Methods

fold :: Monoid m => RAList m -> 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 #

Eq a => Eq (RAList a) Source # 

Methods

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

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

Data a => Data (RAList a) Source # 

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

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 #

Read a => Read (RAList a) Source # 
Show a => Show (RAList a) Source # 

Methods

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

show :: RAList a -> String #

showList :: [RAList a] -> ShowS #

Semigroup (RAList a) Source # 

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 # 

Methods

mempty :: RAList a #

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

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

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).

length :: RAList a -> Word64 Source #

Complexity O(1).

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 -> Top t -> t Source #

lookupM :: forall m a. Monad m => Word64 -> Top a -> m a Source #

lookup :: forall a. Word64 -> Top a -> a Source #

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

List transformations

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

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

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

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

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

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

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

Special folds

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

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

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

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

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

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

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

Building lists

Repetition

Sublists

Extracting sublists

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

drop i l 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 :: Eq a => a -> RAList a -> Bool Source #

notElem :: Eq a => a -> RAList a -> Bool Source #

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

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

Zipping and unzipping lists

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

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

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

Update

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

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

adjust :: (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 :: RAList a -> [a] Source #

Complexity O(n).

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

Complexity O(n).