| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Data.SkewList.Lazy.Internal
Synopsis
- data SkewList a where
- data Tree a
- empty :: SkewList a
- singleton :: a -> SkewList a
- cons :: a -> SkewList a -> SkewList a
- append :: SkewList a -> SkewList a -> SkewList a
- (!) :: HasCallStack => SkewList a -> Int -> a
- (!?) :: SkewList a -> Int -> Maybe a
- uncons :: SkewList a -> Maybe (a, SkewList a)
- length :: SkewList a -> Int
- null :: SkewList a -> Bool
- toList :: SkewList a -> [a]
- fromList :: [a] -> SkewList a
- foldMap :: Monoid m => (a -> m) -> SkewList a -> m
- foldMap' :: Monoid m => (a -> m) -> SkewList a -> m
- foldr :: (a -> b -> b) -> b -> SkewList a -> b
- foldl' :: (b -> a -> b) -> b -> SkewList a -> b
- ifoldMap :: Monoid m => (Int -> a -> m) -> SkewList a -> m
- ifoldr :: (Int -> a -> b -> b) -> b -> SkewList a -> b
- adjust :: Int -> (a -> a) -> SkewList a -> SkewList a
- map :: (a -> b) -> SkewList a -> SkewList b
- imap :: (Int -> a -> b) -> SkewList a -> SkewList b
- itraverse :: Applicative f => (Int -> a -> f b) -> SkewList a -> f (SkewList b)
- valid :: SkewList a -> Bool
- explicitShow :: Show a => SkewList a -> String
- explicitShowsPrec :: Show a => Int -> SkewList a -> ShowS
Documentation
List with efficient random access.
Implemented using skewed binary.
Strict spine, lazy elements variant:
>>>length $ fromList [True, error "bar"]2
Instances
A complete binary tree (completeness not enforced)
Instances
| Foldable Tree Source # | |
Defined in Data.SkewList.Lazy.Internal Methods fold :: Monoid m => Tree m -> m # foldMap :: Monoid m => (a -> m) -> Tree a -> m # foldMap' :: Monoid m => (a -> m) -> Tree a -> m # foldr :: (a -> b -> b) -> b -> Tree a -> b # foldr' :: (a -> b -> b) -> b -> Tree a -> b # foldl :: (b -> a -> b) -> b -> Tree a -> b # foldl' :: (b -> a -> b) -> b -> Tree a -> b # foldr1 :: (a -> a -> a) -> Tree a -> a # foldl1 :: (a -> a -> a) -> Tree a -> a # elem :: Eq a => a -> Tree a -> Bool # maximum :: Ord a => Tree a -> a # | |
| Traversable Tree Source # | |
| Functor Tree Source # | |
| Show a => Show (Tree a) Source # | |
| NFData a => NFData (Tree a) Source # | |
Defined in Data.SkewList.Lazy.Internal | |
| Eq a => Eq (Tree a) Source # | |
| Ord a => Ord (Tree a) Source # | |
| Hashable a => Hashable (Tree a) Source # | |
Defined in Data.SkewList.Lazy.Internal | |
| Strict (Tree a) (Tree a) Source # | |
Construction
append :: SkewList a -> SkewList a -> SkewList a Source #
>>>append (fromList "foo") (fromList "bar")"foobar"
Indexing
(!) :: HasCallStack => SkewList a -> Int -> a infixl 9 Source #
List index.
>>>fromList ['a'..'f'] ! 0'a'
>>>fromList ['a'..'f'] ! 5'f'
>>>fromList ['a'..'f'] ! 6*** Exception: SkewList.! CallStack (from HasCallStack): error... !, called at <interactive>...
(!?) :: SkewList a -> Int -> Maybe a infixl 9 Source #
safe list index.
>>>fromList ['a'..'f'] !? 0Just 'a'
>>>fromList ['a'..'f'] !? 5Just 'f'
>>>fromList ['a'..'f'] !? 6Nothing
Conversions
fromList :: [a] -> SkewList a Source #
Convert ordinary list to SkewList.
>>>fromList ['a' .. 'f']"abcdef"
>>>explicitShow $ fromList ['a' .. 'f']"Cons_ 3 (Nd 'a' (Lf 'b') (Lf 'c')) $ Cons_ 3 (Nd 'd' (Lf 'e') (Lf 'f')) Nil"
>>>explicitShow $ fromList ['a' .. 'e']"Cons_ 1 (Lf 'a') $ Cons_ 1 (Lf 'b') $ Cons_ 3 (Nd 'c' (Lf 'd') (Lf 'e')) Nil"
Folding
Indexed
Mapping
adjust :: Int -> (a -> a) -> SkewList a -> SkewList a Source #
Adjust a value in the list.
>>>adjust 3 toUpper $ fromList "bcdef""bcdEf"
If index is out of bounds, the list is returned unmodified.
>>>adjust 10 toUpper $ fromList "bcdef""bcdef"
>>>adjust (-1) toUpper $ fromList "bcdef""bcdef"
map :: (a -> b) -> SkewList a -> SkewList b Source #
Map over elements.
>>>map toUpper (fromList ['a'..'f'])"ABCDEF"
Indexed
imap :: (Int -> a -> b) -> SkewList a -> SkewList b Source #
Indexed map.
>>>imap (,) $ fromList ['a' .. 'f'][(0,'a'),(1,'b'),(2,'c'),(3,'d'),(4,'e'),(5,'f')]
itraverse :: Applicative f => (Int -> a -> f b) -> SkewList a -> f (SkewList b) Source #
Indexed traverse.
Debug
valid :: SkewList a -> Bool Source #
Check invariants.
- Trees are stored in increasing order.
- Only first two trees can have the same size.
- Tree sizes should be of form
2^n - 1. - Trees should be balanced.