skew-list-0.1: Random access lists: skew binary
Safe HaskellSafe
LanguageHaskell2010

Data.SkewList.Lazy.Internal

Synopsis

Documentation

data SkewList a Source #

List with efficient random access.

Implemented using skewed binary.

Strict spine, lazy elements variant:

>>> length $ fromList [True, error "bar"]
2

Constructors

Nil 
Cons_

Internal constructor. If you use it, maintain invariants (see valid).

Fields

Bundled Patterns

pattern Cons :: a -> SkewList a -> SkewList a

Cons and Nil form complete pattern match.

Instances

Instances details
Arbitrary1 SkewList Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

liftArbitrary :: Gen a -> Gen (SkewList a) #

liftShrink :: (a -> [a]) -> SkewList a -> [SkewList a] #

Foldable SkewList Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

fold :: Monoid m => SkewList m -> m #

foldMap :: Monoid m => (a -> m) -> SkewList a -> m #

foldMap' :: Monoid m => (a -> m) -> SkewList a -> m #

foldr :: (a -> b -> b) -> b -> SkewList a -> b #

foldr' :: (a -> b -> b) -> b -> SkewList a -> b #

foldl :: (b -> a -> b) -> b -> SkewList a -> b #

foldl' :: (b -> a -> b) -> b -> SkewList a -> b #

foldr1 :: (a -> a -> a) -> SkewList a -> a #

foldl1 :: (a -> a -> a) -> SkewList a -> a #

toList :: SkewList a -> [a] #

null :: SkewList a -> Bool #

length :: SkewList a -> Int #

elem :: Eq a => a -> SkewList a -> Bool #

maximum :: Ord a => SkewList a -> a #

minimum :: Ord a => SkewList a -> a #

sum :: Num a => SkewList a -> a #

product :: Num a => SkewList a -> a #

Traversable SkewList Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

traverse :: Applicative f => (a -> f b) -> SkewList a -> f (SkewList b) #

sequenceA :: Applicative f => SkewList (f a) -> f (SkewList a) #

mapM :: Monad m => (a -> m b) -> SkewList a -> m (SkewList b) #

sequence :: Monad m => SkewList (m a) -> m (SkewList a) #

Functor SkewList Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

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

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

FoldableWithIndex Int SkewList Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> SkewList a -> m #

ifoldMap' :: Monoid m => (Int -> a -> m) -> SkewList a -> m #

ifoldr :: (Int -> a -> b -> b) -> b -> SkewList a -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> SkewList a -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> SkewList a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> SkewList a -> b #

FunctorWithIndex Int SkewList Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

imap :: (Int -> a -> b) -> SkewList a -> SkewList b #

TraversableWithIndex Int SkewList Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> SkewList a -> f (SkewList b) #

Arbitrary a => Arbitrary (SkewList a) Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

arbitrary :: Gen (SkewList a) #

shrink :: SkewList a -> [SkewList a] #

CoArbitrary a => CoArbitrary (SkewList a) Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

coarbitrary :: SkewList a -> Gen b -> Gen b #

Function a => Function (SkewList a) Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

function :: (SkewList a -> b) -> SkewList a :-> b #

Monoid (SkewList a) Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

mempty :: SkewList a #

mappend :: SkewList a -> SkewList a -> SkewList a #

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

Semigroup (SkewList a) Source #
>>> fromList "abc" <> fromList "xyz"
"abcxyz"
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

(<>) :: SkewList a -> SkewList a -> SkewList a #

sconcat :: NonEmpty (SkewList a) -> SkewList a #

stimes :: Integral b => b -> SkewList a -> SkewList a #

IsList (SkewList a) Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Associated Types

type Item (SkewList a) #

Methods

fromList :: [Item (SkewList a)] -> SkewList a #

fromListN :: Int -> [Item (SkewList a)] -> SkewList a #

toList :: SkewList a -> [Item (SkewList a)] #

Show a => Show (SkewList a) Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

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

show :: SkewList a -> String #

showList :: [SkewList a] -> ShowS #

NFData a => NFData (SkewList a) Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

rnf :: SkewList a -> () #

Eq a => Eq (SkewList a) Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

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

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

Ord a => Ord (SkewList a) Source #

This instance provides total ordering, but this ordering is not lexicographic. I.e. it is different order than on ordinary lists.

Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

compare :: SkewList a -> SkewList a -> Ordering #

(<) :: SkewList a -> SkewList a -> Bool #

(<=) :: SkewList a -> SkewList a -> Bool #

(>) :: SkewList a -> SkewList a -> Bool #

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

max :: SkewList a -> SkewList a -> SkewList a #

min :: SkewList a -> SkewList a -> SkewList a #

Hashable a => Hashable (SkewList a) Source #

The hash value are different then for an ordinary list:

>>> hash (fromList "foobar") == hash "foobar"
False
>>> hash (fromList "foo", fromList "bar") == hash (fromList "foobar", fromList "")
False
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

hashWithSalt :: Int -> SkewList a -> Int #

hash :: SkewList a -> Int #

Strict (SkewList a) (SkewList a) Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

type Item (SkewList a) Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

type Item (SkewList a) = a

data Tree a Source #

A complete binary tree (completeness not enforced)

Constructors

Lf a 
Nd a !(Tree a) !(Tree a) 

Instances

Instances details
Foldable Tree Source # 
Instance details

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 #

toList :: Tree a -> [a] #

null :: Tree a -> Bool #

length :: Tree a -> Int #

elem :: Eq a => a -> Tree a -> Bool #

maximum :: Ord a => Tree a -> a #

minimum :: Ord a => Tree a -> a #

sum :: Num a => Tree a -> a #

product :: Num a => Tree a -> a #

Traversable Tree Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

traverse :: Applicative f => (a -> f b) -> Tree a -> f (Tree b) #

sequenceA :: Applicative f => Tree (f a) -> f (Tree a) #

mapM :: Monad m => (a -> m b) -> Tree a -> m (Tree b) #

sequence :: Monad m => Tree (m a) -> m (Tree a) #

Functor Tree Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

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

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

Show a => Show (Tree a) Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

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

show :: Tree a -> String #

showList :: [Tree a] -> ShowS #

NFData a => NFData (Tree a) Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

rnf :: Tree a -> () #

Eq a => Eq (Tree a) Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

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

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

Ord a => Ord (Tree a) Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

compare :: Tree a -> Tree a -> Ordering #

(<) :: Tree a -> Tree a -> Bool #

(<=) :: Tree a -> Tree a -> Bool #

(>) :: Tree a -> Tree a -> Bool #

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

max :: Tree a -> Tree a -> Tree a #

min :: Tree a -> Tree a -> Tree a #

Hashable a => Hashable (Tree a) Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

hashWithSalt :: Int -> Tree a -> Int #

hash :: Tree a -> Int #

Strict (Tree a) (Tree a) Source # 
Instance details

Defined in Data.SkewList.Lazy.Internal

Methods

toStrict :: Tree a -> Tree0 a #

toLazy :: Tree0 a -> Tree a #

Construction

empty :: SkewList a Source #

Empty SkewList.

>>> empty :: SkewList Int
[]

singleton :: a -> SkewList a Source #

Single element SkewList.

>>> singleton True
[True]

cons :: a -> SkewList a -> SkewList a Source #

>>> cons 'x' (fromList "foo")
"xfoo"

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'] !? 0
Just 'a'
>>> fromList ['a'..'f'] !? 5
Just 'f'
>>> fromList ['a'..'f'] !? 6
Nothing

uncons :: SkewList a -> Maybe (a, SkewList a) Source #

Inverse of cons.

>>> uncons (fromList ['a'..'f'])
Just ('a',"bcdef")
>>> uncons Nil
Nothing

length :: SkewList a -> Int Source #

Length, O(log n).

null :: SkewList a -> Bool Source #

Is the list empty? O(1).

Conversions

toList :: SkewList a -> [a] Source #

Convert SkewList to ordinary list.

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

foldMap :: Monoid m => (a -> m) -> SkewList a -> m Source #

foldMap' :: Monoid m => (a -> m) -> SkewList a -> m Source #

Strict foldMap.

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

Right fold.

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

Strict left fold.

Indexed

ifoldMap :: Monoid m => (Int -> a -> m) -> SkewList a -> m Source #

Indexed foldMap.

ifoldr :: (Int -> a -> b -> b) -> b -> SkewList a -> b Source #

Indexed right fold.

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.

Orphan instances

Strict (SkewList a) (SkewList a) Source # 
Instance details

Strict (Tree a) (Tree a) Source # 
Instance details

Methods

toStrict :: Tree a -> Tree0 a #

toLazy :: Tree0 a -> Tree a #