Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
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
- data RAList a
- empty :: RAList a
- cons :: a -> RAList a -> RAList a
- uncons :: RAList a -> Maybe (a, RAList a)
- (++) :: RAList a -> RAList a -> RAList a
- head :: RAList a -> Maybe a
- last :: RAList a -> a
- tail :: RAList a -> Maybe (RAList a)
- init :: RAList a -> RAList a
- null :: RAList a -> Bool
- length :: RAList a -> Word64
- (!!) :: RAList a -> Word64 -> a
- lookupWithDefault :: forall t. t -> Word64 -> Top t -> t
- lookupM :: forall (m :: * -> *) a. Monad m => Word64 -> Top a -> m a
- lookup :: forall a. Word64 -> Top a -> a
- lookupL :: Eq a => a -> RAList (a, b) -> Maybe b
- map :: (a -> b) -> RAList a -> RAList b
- reverse :: RAList a -> RAList a
- foldl :: (a -> b -> a) -> a -> RAList b -> a
- foldl' :: (a -> b -> a) -> a -> RAList b -> a
- foldl1 :: (a -> a -> a) -> RAList a -> a
- foldl1' :: (a -> a -> a) -> RAList a -> a
- foldr :: (a -> b -> b) -> b -> RAList a -> b
- foldr1 :: (a -> a -> a) -> RAList a -> a
- concat :: RAList (RAList a) -> RAList a
- concatMap :: (a -> RAList b) -> RAList a -> RAList b
- and :: RAList Bool -> Bool
- or :: RAList Bool -> Bool
- any :: (a -> Bool) -> RAList a -> Bool
- all :: (a -> Bool) -> RAList a -> Bool
- sum :: Num a => RAList a -> a
- product :: Num a => RAList a -> a
- maximum :: Ord a => RAList a -> a
- minimum :: Ord a => RAList a -> a
- replicate :: Word64 -> a -> RAList a
- take :: Word64 -> RAList a -> RAList a
- drop :: Word64 -> RAList a -> RAList a
- simpleDrop :: Word64 -> RAList a -> RAList a
- splitAt :: Word64 -> RAList a -> (RAList a, RAList a)
- elem :: Eq a => a -> RAList a -> Bool
- notElem :: Eq a => a -> RAList a -> Bool
- filter :: (a -> Bool) -> RAList a -> RAList a
- partition :: (a -> Bool) -> RAList a -> (RAList a, RAList a)
- zip :: RAList a -> RAList b -> RAList (a, b)
- zipWith :: (a -> b -> c) -> RAList a -> RAList b -> RAList c
- unzip :: RAList (a, b) -> (RAList a, RAList b)
- update :: Word64 -> a -> RAList a -> RAList a
- adjust :: (a -> a) -> Word64 -> RAList a -> RAList a
- toList :: RAList a -> [a]
- fromList :: [a] -> RAList a
Documentation
Instances
Monad RAList Source # | |
Functor RAList Source # | |
Applicative RAList Source # | |
Foldable RAList Source # | |
Defined in Data.RAList 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 # elem :: Eq a => a -> RAList a -> Bool # maximum :: Ord a => RAList a -> a # minimum :: Ord a => RAList a -> a # | |
Traversable RAList Source # | |
Eq a => Eq (RAList a) Source # | |
Data a => Data (RAList a) Source # | |
Defined in Data.RAList 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 # | |
Defined in Data.RAList | |
Read a => Read (RAList a) Source # | |
Show a => Show (RAList a) Source # | |
Semigroup (RAList a) Source # | |
Monoid (RAList a) Source # | |
Basic functions
Indexing lists
These functions treat a list xs
as a indexed collection,
with indices ranging from 0 to
.length
xs - 1
lookupWithDefault :: forall t. t -> Word64 -> Top t -> t Source #
List transformations
Special folds
Building lists
Repetition
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)).drop
i l
Searching lists
Searching by equality
Zipping and unzipping lists
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).