EdisonCore-1.2.1.3: A library of efficent, purely-functional data structures (Core Implementations)

PortabilityGHC, Hugs (MPTC and FD)
Stabilitystable
Maintainerrobdockins AT fastmail DOT fm

Data.Edison.Seq.BraunSeq

Contents

Description

One-sided Braun sequences. All running times are as listed in Data.Edison.Seq except the following:

  • lview, lcons, ltail* O( log n )
  • rcons, rview, rhead*, rtail*, size O( log^2 n )
  • copy, inBounds, lookup*, update, adjust O( log i )
  • append O( n1 log n2 )
  • concat O( n + m log m )
  • drop, splitAt O( i log n )
  • subseq O( i log n + len )
  • reverseOnto O( n1 log n2 )
  • concatMap, (>>=) O( n * t + m log m ), where n is the length of the input sequence m is the length of the output sequence and t is the running time of f

By keeping track of the size, we could get rcons, rview, rhead*, and rtail* down to O(log n) as well; furthermore, size would be O( 1 ).

References:

  • Rob Hoogerwoord. "A symmetric set of efficient list operations". Journal of Functional Programming, 2(4):505--513, 1992.
  • Rob Hoogerwoord. "A Logarithmic Implementation of Flexible Arrays". Mathematics of Program Construction (MPC'92), pages 191-207.
  • Chris Okasaki. "Three algorithms on Braun Trees". Journal of Function Programming 7(6):661-666. Novemebr 1997.

Synopsis

Sequence Type

data Seq a Source

Instances

Monad Seq 
Functor Seq 
MonadPlus Seq 
Sequence Seq 
Eq a => Eq (Seq a) 
Ord a => Ord (Seq a) 
Read a => Read (Seq a) 
Show a => Show (Seq a) 
Arbitrary a => Arbitrary (Seq a) 
Monoid (Seq a) 

Sequence Operations

lcons :: a -> Seq a -> Seq aSource

rcons :: a -> Seq a -> Seq aSource

append :: Seq a -> Seq a -> Seq aSource

lview :: Monad m => Seq a -> m (a, Seq a)Source

lhead :: Seq a -> aSource

ltail :: Seq a -> Seq aSource

rview :: Monad m => Seq a -> m (a, Seq a)Source

rhead :: Seq a -> aSource

rtail :: Seq a -> Seq aSource

lheadM :: Monad m => Seq a -> m aSource

ltailM :: Monad m => Seq a -> m (Seq a)Source

rheadM :: Monad m => Seq a -> m aSource

rtailM :: Monad m => Seq a -> m (Seq a)Source

concat :: Seq (Seq a) -> Seq aSource

reverseOnto :: Seq a -> Seq a -> Seq aSource

fromList :: [a] -> Seq aSource

toList :: Seq a -> [a]Source

map :: (a -> b) -> Seq a -> Seq bSource

concatMap :: (a -> Seq b) -> Seq a -> Seq bSource

fold :: (a -> b -> b) -> b -> Seq a -> bSource

fold' :: (a -> b -> b) -> b -> Seq a -> bSource

fold1 :: (a -> a -> a) -> Seq a -> aSource

fold1' :: (a -> a -> a) -> Seq a -> aSource

foldr :: (a -> b -> b) -> b -> Seq a -> bSource

foldr' :: (a -> b -> b) -> b -> Seq a -> bSource

foldl :: (b -> a -> b) -> b -> Seq a -> bSource

foldl' :: (b -> a -> b) -> b -> Seq a -> bSource

foldr1 :: (a -> a -> a) -> Seq a -> aSource

foldr1' :: (a -> a -> a) -> Seq a -> aSource

foldl1 :: (a -> a -> a) -> Seq a -> aSource

foldl1' :: (a -> a -> a) -> Seq a -> aSource

reducer :: (a -> a -> a) -> a -> Seq a -> aSource

reducer' :: (a -> a -> a) -> a -> Seq a -> aSource

reducel :: (a -> a -> a) -> a -> Seq a -> aSource

reducel' :: (a -> a -> a) -> a -> Seq a -> aSource

reduce1 :: (a -> a -> a) -> Seq a -> aSource

reduce1' :: (a -> a -> a) -> Seq a -> aSource

copy :: Int -> a -> Seq aSource

lookup :: Int -> Seq a -> aSource

lookupM :: Monad m => Int -> Seq a -> m aSource

lookupWithDefault :: a -> Int -> Seq a -> aSource

update :: Int -> a -> Seq a -> Seq aSource

adjust :: (a -> a) -> Int -> Seq a -> Seq aSource

mapWithIndex :: (Int -> a -> b) -> Seq a -> Seq bSource

foldrWithIndex :: (Int -> a -> b -> b) -> b -> Seq a -> bSource

foldrWithIndex' :: (Int -> a -> b -> b) -> b -> Seq a -> bSource

foldlWithIndex :: (b -> Int -> a -> b) -> b -> Seq a -> bSource

foldlWithIndex' :: (b -> Int -> a -> b) -> b -> Seq a -> bSource

take :: Int -> Seq a -> Seq aSource

drop :: Int -> Seq a -> Seq aSource

splitAt :: Int -> Seq a -> (Seq a, Seq a)Source

subseq :: Int -> Int -> Seq a -> Seq aSource

filter :: (a -> Bool) -> Seq a -> Seq aSource

partition :: (a -> Bool) -> Seq a -> (Seq a, Seq a)Source

takeWhile :: (a -> Bool) -> Seq a -> Seq aSource

dropWhile :: (a -> Bool) -> Seq a -> Seq aSource

splitWhile :: (a -> Bool) -> Seq a -> (Seq a, Seq a)Source

zip :: Seq a -> Seq b -> Seq (a, b)Source

zip3 :: Seq a -> Seq b -> Seq c -> Seq (a, b, c)Source

zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq cSource

zipWith3 :: (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq dSource

unzip :: Seq (a, b) -> (Seq a, Seq b)Source

unzip3 :: Seq (a, b, c) -> (Seq a, Seq b, Seq c)Source

unzipWith :: (a -> b) -> (a -> c) -> Seq a -> (Seq b, Seq c)Source

unzipWith3 :: (a -> b) -> (a -> c) -> (a -> d) -> Seq a -> (Seq b, Seq c, Seq d)Source

strict :: Seq a -> Seq aSource

strictWith :: (a -> b) -> Seq a -> Seq aSource

Unit testing

Documentation