Copyright | Copyright (c) 1998-1999 2008 Chris Okasaki |
---|---|
License | MIT; see COPYRIGHT file for terms and conditions |
Maintainer | robdockins AT fastmail DOT fm |
Stability | stable |
Portability | GHC, Hugs (MPTC and FD) |
Safe Haskell | None |
Language | Haskell2010 |
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 )
, wheren
is the length of the input sequencem
is the length of the output sequence andt
is the running time off
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.
- data Seq a
- empty :: Seq a
- singleton :: a -> Seq a
- lcons :: a -> Seq a -> Seq a
- rcons :: a -> Seq a -> Seq a
- append :: Seq a -> Seq a -> Seq a
- lview :: Monad m => Seq a -> m (a, Seq a)
- lhead :: Seq a -> a
- ltail :: Seq a -> Seq a
- rview :: Monad m => Seq a -> m (a, Seq a)
- rhead :: Seq a -> a
- rtail :: Seq a -> Seq a
- lheadM :: Monad m => Seq a -> m a
- ltailM :: Monad m => Seq a -> m (Seq a)
- rheadM :: Monad m => Seq a -> m a
- rtailM :: Monad m => Seq a -> m (Seq a)
- null :: Seq a -> Bool
- size :: Seq a -> Int
- concat :: Seq (Seq a) -> Seq a
- reverse :: Seq a -> Seq a
- reverseOnto :: Seq a -> Seq a -> Seq a
- fromList :: [a] -> Seq a
- toList :: Seq a -> [a]
- map :: (a -> b) -> Seq a -> Seq b
- concatMap :: (a -> Seq b) -> Seq a -> Seq b
- fold :: (a -> b -> b) -> b -> Seq a -> b
- fold' :: (a -> b -> b) -> b -> Seq a -> b
- fold1 :: (a -> a -> a) -> Seq a -> a
- fold1' :: (a -> a -> a) -> Seq a -> a
- foldr :: (a -> b -> b) -> b -> Seq a -> b
- foldr' :: (a -> b -> b) -> b -> Seq a -> b
- foldl :: (b -> a -> b) -> b -> Seq a -> b
- foldl' :: (b -> a -> b) -> b -> Seq a -> b
- foldr1 :: (a -> a -> a) -> Seq a -> a
- foldr1' :: (a -> a -> a) -> Seq a -> a
- foldl1 :: (a -> a -> a) -> Seq a -> a
- foldl1' :: (a -> a -> a) -> Seq a -> a
- reducer :: (a -> a -> a) -> a -> Seq a -> a
- reducer' :: (a -> a -> a) -> a -> Seq a -> a
- reducel :: (a -> a -> a) -> a -> Seq a -> a
- reducel' :: (a -> a -> a) -> a -> Seq a -> a
- reduce1 :: (a -> a -> a) -> Seq a -> a
- reduce1' :: (a -> a -> a) -> Seq a -> a
- copy :: Int -> a -> Seq a
- inBounds :: Int -> Seq a -> Bool
- lookup :: Int -> Seq a -> a
- lookupM :: Monad m => Int -> Seq a -> m a
- lookupWithDefault :: a -> Int -> Seq a -> a
- update :: Int -> a -> Seq a -> Seq a
- adjust :: (a -> a) -> Int -> Seq a -> Seq a
- mapWithIndex :: (Int -> a -> b) -> Seq a -> Seq b
- foldrWithIndex :: (Int -> a -> b -> b) -> b -> Seq a -> b
- foldrWithIndex' :: (Int -> a -> b -> b) -> b -> Seq a -> b
- foldlWithIndex :: (b -> Int -> a -> b) -> b -> Seq a -> b
- foldlWithIndex' :: (b -> Int -> a -> b) -> b -> Seq a -> b
- take :: Int -> Seq a -> Seq a
- drop :: Int -> Seq a -> Seq a
- splitAt :: Int -> Seq a -> (Seq a, Seq a)
- subseq :: Int -> Int -> Seq a -> Seq a
- filter :: (a -> Bool) -> Seq a -> Seq a
- partition :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
- takeWhile :: (a -> Bool) -> Seq a -> Seq a
- dropWhile :: (a -> Bool) -> Seq a -> Seq a
- splitWhile :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
- zip :: Seq a -> Seq b -> Seq (a, b)
- zip3 :: Seq a -> Seq b -> Seq c -> Seq (a, b, c)
- zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c
- zipWith3 :: (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d
- unzip :: Seq (a, b) -> (Seq a, Seq b)
- unzip3 :: Seq (a, b, c) -> (Seq a, Seq b, Seq c)
- unzipWith :: (a -> b) -> (a -> c) -> Seq a -> (Seq b, Seq c)
- unzipWith3 :: (a -> b) -> (a -> c) -> (a -> d) -> Seq a -> (Seq b, Seq c, Seq d)
- strict :: Seq a -> Seq a
- strictWith :: (a -> b) -> Seq a -> Seq a
- structuralInvariant :: Seq a -> Bool
- moduleName :: String
Sequence Type
Monad Seq Source # | |
Functor Seq Source # | |
Applicative Seq Source # | |
Sequence Seq Source # | |
Alternative Seq Source # | |
MonadPlus Seq Source # | |
Eq a => Eq (Seq a) Source # | |
Ord a => Ord (Seq a) Source # | |
Read a => Read (Seq a) Source # | |
Show a => Show (Seq a) Source # | |
Semigroup (Seq a) Source # | |
Monoid (Seq a) Source # | |
Arbitrary a => Arbitrary (Seq a) Source # | |
CoArbitrary a => CoArbitrary (Seq a) Source # | |
Sequence Operations
lookupWithDefault :: a -> Int -> Seq a -> a Source #
foldrWithIndex :: (Int -> a -> b -> b) -> b -> Seq a -> b Source #
foldrWithIndex' :: (Int -> a -> b -> b) -> b -> Seq a -> b Source #
foldlWithIndex :: (b -> Int -> a -> b) -> b -> Seq a -> b Source #
foldlWithIndex' :: (b -> Int -> a -> b) -> b -> Seq a -> b Source #
strictWith :: (a -> b) -> Seq a -> Seq a Source #
Unit testing
structuralInvariant :: Seq a -> Bool Source #
Documentation
moduleName :: String Source #