slist-0.1.1.0: Sized list
Copyright(c) 2019-2020 Veronika Romashkina
LicenseMPL-2.0
MaintainerVeronika Romashkina <vrom911@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Slist

Description

This module introduces sized list data type — Slist. The data type has the following shape:

data Slist a = Slist
    { sList :: [a]
    , sSize :: Size
    }

As you can see along with the familiar list, it contains Size field that represents the size of the structure. Slists can be finite or infinite, and this is expressed with Size.

data Size
    = Size Int
    | Infinity

This representation of the list gives some additional advantages. Getting the length of the list is the "free" operation (runs in \( O(1) \)). This property helps to improve the performance for a bunch of functions like take, drop, at, etc. But also it doesn't actually add any overhead on the existing functions.

Also, this allows to write a number of safe functions like safeReverse, safeHead, safeLast, safeIsSuffixOf, etc.

Comparison

Check out the comparison table between lists and slists performance.

Function list (finite) list (infinite) Slist (finite) Slist (infinite)
length \( O(n) \) <hangs> \( O(1) \) \( O(1) \)
safeLast \( O(n) \) <hangs> \( O(n) \) \( O(1) \)
init \( O(n) \) <hangs> \( O(n) \) \( O(1) \)
take \( O(min\ i\ n) \) \( O(i) \) 0 < i < n: \(O(i)\) otherwise: \(O(1)\) \(O(i)\)
at \( O(min\ i\ n) \) run-time exception \( O(i) \) run-time exception 0 < i < n: \(O(i)\) otherwise: \(O(1)\) \( O(i) \)
safeStripPrefix \( O(m) \) \( O(m) \) can hang \( O(m) \) \( O(m) \)

Potential usage cases

  • When you ask the length of the list too frequently.
  • When you need to convert to data structures that require to know the list size in advance for allocating an array of the elements. Example: Vector data structure.
  • When you need to serialised lists.
  • When you need to control the behaviour depending on the finiteness of the list.
  • When you need a more efficient or safe implementation of some functions.
Synopsis

Types

data Slist a Source #

Data type that represents sized list. Size can be both finite or infinite, it is established using Size data type.

Instances

Instances details
Monad Slist Source # 
Instance details

Defined in Slist

Methods

(>>=) :: Slist a -> (a -> Slist b) -> Slist b #

(>>) :: Slist a -> Slist b -> Slist b #

return :: a -> Slist a #

Functor Slist Source # 
Instance details

Defined in Slist

Methods

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

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

Applicative Slist Source # 
Instance details

Defined in Slist

Methods

pure :: a -> Slist a #

(<*>) :: Slist (a -> b) -> Slist a -> Slist b #

liftA2 :: (a -> b -> c) -> Slist a -> Slist b -> Slist c #

(*>) :: Slist a -> Slist b -> Slist b #

(<*) :: Slist a -> Slist b -> Slist a #

Foldable Slist Source #

Efficient implementation of sum and product functions. length returns Ints maxBound on infinite lists.

Instance details

Defined in Slist

Methods

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

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

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

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

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

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

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

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

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

toList :: Slist a -> [a] #

null :: Slist a -> Bool #

length :: Slist a -> Int #

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

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

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

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

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

Traversable Slist Source # 
Instance details

Defined in Slist

Methods

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

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

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

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

Alternative Slist Source # 
Instance details

Defined in Slist

Methods

empty :: Slist a #

(<|>) :: Slist a -> Slist a -> Slist a #

some :: Slist a -> Slist [a] #

many :: Slist a -> Slist [a] #

IsList (Slist a) Source # 
Instance details

Defined in Slist

Associated Types

type Item (Slist a) #

Methods

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

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

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

Eq a => Eq (Slist a) Source #

Equality of sized lists is checked more efficiently due to the fact that the check on the list sizes can be done first for the constant time.

Instance details

Defined in Slist

Methods

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

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

Ord a => Ord (Slist a) Source #

Lexicographical comparison of the lists.

Instance details

Defined in Slist

Methods

compare :: Slist a -> Slist a -> Ordering #

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

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

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

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

max :: Slist a -> Slist a -> Slist a #

min :: Slist a -> Slist a -> Slist a #

Read a => Read (Slist a) Source # 
Instance details

Defined in Slist

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

Defined in Slist

Methods

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

show :: Slist a -> String #

showList :: [Slist a] -> ShowS #

Semigroup (Slist a) Source #

List appending. Use <> for Slist concatenation instead of ++ operator that is common in ordinary list concatenations.

Instance details

Defined in Slist

Methods

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

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

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

Monoid (Slist a) Source # 
Instance details

Defined in Slist

Methods

mempty :: Slist a #

mappend :: Slist a -> Slist a -> Slist a #

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

type Item (Slist a) Source # 
Instance details

Defined in Slist

type Item (Slist a) = a

data Size Source #

Data type that represents lists size/lengths.

List length Size
[] 0 Size 0
[1..10] 10 Size 10
[1..] hangs Infinity

Note, that size is not suppose to have negative value, so use the Size constructor carefully.

Instances

Instances details
Bounded Size Source #

The minimum possible size for the list is empty list: Size 0 The maximum possible size is Infinity.

Instance details

Defined in Slist.Size

Eq Size Source # 
Instance details

Defined in Slist.Size

Methods

(==) :: Size -> Size -> Bool #

(/=) :: Size -> Size -> Bool #

Num Size Source #

Efficient implementations of numeric operations with Sizes.

Any operations with Infinity size results into Infinity.

TODO: checking on overflow when + or * sizes.

Instance details

Defined in Slist.Size

Methods

(+) :: Size -> Size -> Size #

(-) :: Size -> Size -> Size #

(*) :: Size -> Size -> Size #

negate :: Size -> Size #

abs :: Size -> Size #

signum :: Size -> Size #

fromInteger :: Integer -> Size #

Ord Size Source # 
Instance details

Defined in Slist.Size

Methods

compare :: Size -> Size -> Ordering #

(<) :: Size -> Size -> Bool #

(<=) :: Size -> Size -> Bool #

(>) :: Size -> Size -> Bool #

(>=) :: Size -> Size -> Bool #

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

Read Size Source # 
Instance details

Defined in Slist.Size

Show Size Source # 
Instance details

Defined in Slist.Size

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

Smart constructors

slist :: [a] -> Slist a Source #

O(n). Constructs Slist from the given list.

>>> slist [1..5]
Slist {sList = [1,2,3,4,5], sSize = Size 5}

Note: works with finite lists. Use infiniteSlist to construct infinite lists.

infiniteSlist :: [a] -> Slist a Source #

O(1). Constructs Slist from the given list.

>> infiniteSlist [1..]
Slist {sList = [1..], sSize = Infinity}

Note: works with infinite lists. Use slist to construct finite lists.

one :: a -> Slist a Source #

O(1). Creates Slist with a single element. The size of such Slist is always equals to Size 1.

>>> one "and only"
Slist {sList = ["and only"], sSize = Size 1}

iterate :: (a -> a) -> a -> Slist a Source #

Returns an infinite slist of repeated applications of the given function to the start element:

iterate f x == [x, f x, f (f x), ...]
>> iterate (+1) 0
Slist {sList = [0..], sSize = Infinity}
>>> take 5 $ iterate ('a':) "a"
Slist {sList = ["a","aa","aaa","aaaa","aaaaa"], sSize = Size 5}

Note: iterate is lazy, potentially leading to thunk build-up if the consumer doesn't force each iterate. See iterate' for a strict variant of this function.

iterate' :: (a -> a) -> a -> Slist a Source #

Returns an infinite slist of repeated applications of the given function to the start element:

iterate' f x == [x, f x, f (f x), ...]
>> iterate' (+1) 0
Slist {sList = [0..], sSize = Infinity}
>>> take 5 $ iterate' ('a':) "a"
Slist {sList = ["a","aa","aaa","aaaa","aaaaa"], sSize = Size 5}

iterate' is the strict version of iterate.

It ensures that the result of each application of force to weak head normal form before proceeding.

repeat :: a -> Slist a Source #

O(1). Creates an infinite slist with the given element at each position.

>> repeat 42
Slist {sList = [42, 42 ..], sSize = Infinity}
>>> take 6 $ repeat 'm'
Slist {sList = "mmmmmm", sSize = Size 6}

replicate :: Int -> a -> Slist a Source #

O(n). Creates a finite slist with the given value at each position.

>>> replicate 3 'o'
Slist {sList = "ooo", sSize = Size 3}
>>> replicate (-11) "hmm"
Slist {sList = [], sSize = Size 0}

cycle :: Slist a -> Slist a Source #

Ties a finite list into a circular one, or equivalently, the infinite repetition of the original list. It is the identity on infinite lists.

>>> take 23 $ cycle (slist "pam ")
Slist {sList = "pam pam pam pam pam pam", sSize = Size 23}
>> cycle $ infiniteSlist [1..]
Slist {sList = [1..], sSize = Infinity}

fromRange :: Enum a => a -> a -> Slist a Source #

O(1). An slist equivalent of enumFromTo function or [from..to] notation: creates an Slist of sequentially ordered values starting at from and ending at to inclusively.

>>> fromRange 0 5
Slist {sList = [0,1,2,3,4,5], sSize = Size 6}
>>> fromRange 5 0
Slist {sList = [], sSize = Size 0}
>>> fromRange 0 0
Slist {sList = [0], sSize = Size 1}
>>> fromRange 'a' 'd'
Slist {sList = "abcd", sSize = Size 4}

Basic functions

len :: Slist a -> Int Source #

O(1). Returns the length of a structure as an Int. On infinite lists returns the Ints maxBound.

>>> len $ one 42
1
>>> len $ slist [1..3]
3
>>> len $ infiniteSlist [1..]
9223372036854775807

size :: Slist a -> Size Source #

O(1). Returns the Size of the slist.

>>> size $ slist "Hello World!"
Size 12
>>> size $ infiniteSlist [1..]
Infinity

isEmpty :: Slist a -> Bool Source #

O(1). Checks if Slist is empty

>>> isEmpty mempty
True
>>> isEmpty $ slist []
True
>>> isEmpty $ slist "Not Empty"
False

head :: Slist a -> a Source #

O(1). Extracts the first element of a slist. Uses not total head function, so use wisely.

It is recommended to use safeHead instead.

>>> head $ slist "qwerty"
'q'
>>> head $ infiniteSlist [1..]
1
>>> head mempty
*** Exception: Prelude.head: empty list

safeHead :: Slist a -> Maybe a Source #

O(1). Extracts the first element of a slist if possible.

>>> safeHead $ slist "qwerty"
Just 'q'
>>> safeHead $ infiniteSlist [1..]
Just 1
>>> safeHead mempty
Nothing

last :: Slist a -> a Source #

O(n). Extracts the last element of a list. Uses not total last function, so use wisely.

It is recommended to use safeLast instead

>>> last $ slist "qwerty"
'y'
>>> last mempty
*** Exception: Prelude.last: empty list
>> last $ infiniteSlist [1..]
<hangs>

safeLast :: Slist a -> Maybe a Source #

O(n). Extracts the last element of a list if possible.

>>> safeLast $ slist "qwerty"
Just 'y'
>>> safeLast mempty
Nothing
>>> safeLast $ infiniteSlist [1..]
Nothing

init :: Slist a -> Slist a Source #

O(n). Return all the elements of a list except the last one.

>>> init mempty
Slist {sList = [], sSize = Size 0}
>>> init $ slist "Hello"
Slist {sList = "Hell", sSize = Size 4}
>> init $ infiniteSlist [0..]
Slist {sList = [0..], sSize = Infinity}

tail :: Slist a -> Slist a Source #

O(1). Returns a slist with all the elements after the head of a given slist.

>>> tail mempty
Slist {sList = [], sSize = Size 0}
>>> tail $ slist "Hello"
Slist {sList = "ello", sSize = Size 4}
>> tail $ infiniteSlist [0..]
Slist {sList = [1..], sSize = Infinity}

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

O(1). Decomposes a slist into its head and tail. If the slist is empty, returns Nothing.

>>> uncons mempty
Nothing
>>> uncons $ one 'a'
Just ('a',Slist {sList = "", sSize = Size 0})
>> uncons $ infiniteSlist [0..]
Just (0, Slist {sList = [1..], sSize = Infinity})

Transformations

map :: (a -> b) -> Slist a -> Slist b Source #

O(n). Applies the given function to each element of the slist.

map f (slist [x1, x2, ..., xn])     == slist [f x1, f x2, ..., f xn]
map f (infiniteSlist [x1, x2, ...]) == infiniteSlist [f x1, f x2, ...]

reverse :: Slist a -> Slist a Source #

O(n). Returns the elements of the slist in reverse order.

>>> reverse $ slist "Hello"
Slist {sList = "olleH", sSize = Size 5}
>>> reverse $ slist "wow"
Slist {sList = "wow", sSize = Size 3}

Note: reverse slist can not be calculated on infinite slists.

>> reverse $ infiniteSlist [1..]
<hangs>

Use safeReverse to not hang on infinite slists.

safeReverse :: Slist a -> Slist a Source #

O(n). Returns the elements of the slist in reverse order. On infinite slists returns the initial slist.

>>> safeReverse $ slist "Hello"
Slist {sList = "olleH", sSize = Size 5}
>> reverse $ infiniteSlist [1..]
Slist {sList = [1..], sSize = Infinity}

intersperse :: a -> Slist a -> Slist a Source #

O(n). Takes an element and a list and intersperses that element between the elements of the list.

>>> intersperse ',' $ slist "abcd"
Slist {sList = "a,b,c,d", sSize = Size 7}
>>> intersperse '!' mempty
Slist {sList = "", sSize = Size 0}
>> intersperse 0 $ infiniteSlist [1,1..]
Slist {sList = [1,0,1,0..], sSize = Infinity}

intercalate :: Slist a -> Slist (Slist a) -> Slist a Source #

O(n). Inserts the given slist in between the slists and concatenates the result.

intercalate x xs = concat (intersperse x xs)
>>> intercalate (slist ", ") $ slist [slist "Lorem", slist "ipsum", slist "dolor"]
Slist {sList = "Lorem, ipsum, dolor", sSize = Size 19}

transpose :: Slist (Slist a) -> Slist (Slist a) Source #

O(n * m). Transposes the rows and columns of the slist.

>>> transpose $ slist [slist [1,2]]
Slist {sList = [Slist {sList = [1], sSize = Size 1},Slist {sList = [2], sSize = Size 1}], sSize = Size 2}
>> transpose $ slist [slist [1,2,3], slist [4,5,6]]
Slist { sList =
          [ Slist {sList = [1,4], sSize = Size 2}
          , Slist {sList = [2,5], sSize = Size 2}
          , Slist {sList = [3,6], sSize = Size 2}
          ]
      , sSize = Size 3
      }

If some of the rows are shorter than the following rows, their elements are skipped:

>>> transpose $ slist [slist [10,11], slist [20], mempty]
Slist {sList = [Slist {sList = [10,20], sSize = Size 2},Slist {sList = [11], sSize = Size 1}], sSize = Size 2}

If some of the rows is an infinite slist, then the resulting slist is going to be infinite.

subsequences :: Slist a -> Slist (Slist a) Source #

O(2 ^ n). Returns the list of all subsequences of the argument.

>>> subsequences mempty
Slist {sList = [Slist {sList = [], sSize = Size 0}], sSize = Size 1}
>>> subsequences $ slist "ab"
Slist {sList = [Slist {sList = "", sSize = Size 0},Slist {sList = "a", sSize = Size 1},Slist {sList = "b", sSize = Size 1},Slist {sList = "ab", sSize = Size 2}], sSize = Size 4}
>>> take 4 $ subsequences $ infiniteSlist [1..]
Slist {sList = [Slist {sList = [], sSize = Size 0},Slist {sList = [1], sSize = Size 1},Slist {sList = [2], sSize = Size 1},Slist {sList = [1,2], sSize = Size 2}], sSize = Size 4}

permutations :: Slist a -> Slist (Slist a) Source #

O(n!). Returns the list of all permutations of the argument.

>>> permutations mempty
Slist {sList = [Slist {sList = [], sSize = Size 0}], sSize = Size 1}
>>> permutations $ slist "abc"
Slist {sList = [Slist {sList = "abc", sSize = Size 3},Slist {sList = "bac", sSize = Size 3},Slist {sList = "cba", sSize = Size 3},Slist {sList = "bca", sSize = Size 3},Slist {sList = "cab", sSize = Size 3},Slist {sList = "acb", sSize = Size 3}], sSize = Size 6}

Reducing slists (folds)

concat :: Foldable t => t (Slist a) -> Slist a Source #

\( O(\sum n_i) \) The concatenation of all the elements of a container of slists.

>>> concat [slist [1,2], slist [3..5], slist [6..10]]
Slist {sList = [1,2,3,4,5,6,7,8,9,10], sSize = Size 10}
>>  concat $ slist [slist [1,2], infiniteSlist [3..]]
Slist {sList = [1..], sSize = Infinity}

concatMap :: Foldable t => (a -> Slist b) -> t a -> Slist b Source #

Maps a function over all the elements of a container and concatenates the resulting slists.

>>> concatMap one "abc"
Slist {sList = "abc", sSize = Size 3}

Building slists

Scans

scanl :: (b -> a -> b) -> b -> Slist a -> Slist b Source #

O(n). Similar to foldl, but returns a slist of successive reduced values from the left:

scanl f z $ slist [x1, x2, ...] == slist [z, z `f` x1, (z `f` x1) `f` x2, ...]

Note that

last (scanl f z xs) == foldl f z xs.

This peculiar arrangement is necessary to prevent scanl being rewritten in its own right-hand side.

>>> scanl (+) 0 $ slist [1..10]
Slist {sList = [0,1,3,6,10,15,21,28,36,45,55], sSize = Size 11}

scanl' :: (b -> a -> b) -> b -> Slist a -> Slist b Source #

O(n). A strictly accumulating version of scanl

scanl1 :: (a -> a -> a) -> Slist a -> Slist a Source #

O(n). scanl1 is a variant of scanl that has no starting value argument:

scanl1 f $ slist [x1, x2, ...] == slist [x1, x1 `f` x2, ...]

scanr :: (a -> b -> b) -> b -> Slist a -> Slist b Source #

O(n). The right-to-left dual of scanl.

Note that

head (scanr f z xs) == foldr f z xs.
>>> scanr (+) 0 $ slist [1..10]
Slist {sList = [55,54,52,49,45,40,34,27,19,10,0], sSize = Size 11}

scanr1 :: (a -> a -> a) -> Slist a -> Slist a Source #

A variant of scanr that has no starting value argument.

Unfolding

unfoldr :: forall a b. (b -> Maybe (a, b)) -> b -> Slist a Source #

O(n). A `dual' to foldr: while foldr reduces a list to a summary value, unfoldr builds a list from a seed value. The function takes the element and returns Nothing if it is done producing the list or returns Just (a,b), in which case, a is a prepended to the list and b is used as the next element in a recursive call.

In some cases, unfoldr can undo a foldr operation:

unfoldr f' (foldr f z xs) == xs

if the following holds:

f' (f x y) = Just (x,y)
f' z       = Nothing

A simple use of unfoldr:

>>> unfoldr (\b -> if b == 0 then Nothing else Just (b, b-1)) 10
Slist {sList = [10,9,8,7,6,5,4,3,2,1], sSize = Size 10}

Subslists

Extracting

take :: Int -> Slist a -> Slist a Source #

O(i) | i < n and O(1) | otherwise.

Returns the prefix of the slist of the given length. If the given i is non-positive then the empty structure is returned. If i is exceeds the length of the structure the initial slist is returned.

>>> take 5 $ slist "Hello world!"
Slist {sList = "Hello", sSize = Size 5}
>>> take 20 $ slist "small"
Slist {sList = "small", sSize = Size 5}
>>> take 0 $ slist "none"
Slist {sList = "", sSize = Size 0}
>>> take (-11) $ slist "hmm"
Slist {sList = "", sSize = Size 0}
>>> take 4 $ infiniteSlist [1..]
Slist {sList = [1,2,3,4], sSize = Size 4}

drop :: Int -> Slist a -> Slist a Source #

O(i) | i < n and O(1) | otherwise.

Returns the suffix of the slist after the first i elements. If i exceeds the length of the slist then the empty structure is returned. If i is non-positive the initial structure is returned.

>>> drop 6 $ slist "Hello World"
Slist {sList = "World", sSize = Size 5}
>>> drop 42 $ slist "oops!"
Slist {sList = "", sSize = Size 0}
>>> drop 0 $ slist "Hello World!"
Slist {sList = "Hello World!", sSize = Size 12}
>>> drop (-4) $ one 42
Slist {sList = [42], sSize = Size 1}
>> drop 5 $ infiniteSlist [1..]
Slist {sList = [6..], sSize = Infinity}

splitAt :: Int -> Slist a -> (Slist a, Slist a) Source #

O(i) | i < n and O(1) | otherwise.

Returns a tuple where the first element is the prefix of the given length and the second element is the remainder of the slist.

>>> splitAt 5 $ slist "Hello World!"
(Slist {sList = "Hello", sSize = Size 5},Slist {sList = " World!", sSize = Size 7})
>>> splitAt 0 $ slist "abc"
(Slist {sList = "", sSize = Size 0},Slist {sList = "abc", sSize = Size 3})
>>> splitAt 4 $ slist "abc"
(Slist {sList = "abc", sSize = Size 3},Slist {sList = "", sSize = Size 0})
>>> splitAt (-42) $ slist "??"
(Slist {sList = "", sSize = Size 0},Slist {sList = "??", sSize = Size 2})
>> splitAt 2 $ infiniteSlist [1..]
(Slist {sList = [1,2], sSize = Size 2}, Slist {sList = [3..], sSize = Infinity})

takeWhile :: forall a. (a -> Bool) -> Slist a -> Slist a Source #

O(n). Returns the longest prefix (possibly empty) of elements that satisfy the given predicate.

>>> takeWhile (<3) $ slist [1..10]
Slist {sList = [1,2], sSize = Size 2}
>>> takeWhile (<3) $ infiniteSlist [1..]
Slist {sList = [1,2], sSize = Size 2}
>>> takeWhile (<=10) $ slist [1..10]
Slist {sList = [1,2,3,4,5,6,7,8,9,10], sSize = Size 10}
>>> takeWhile (<0) $ slist [1..10]
Slist {sList = [], sSize = Size 0}

dropWhile :: forall a. (a -> Bool) -> Slist a -> Slist a Source #

O(n). Returns the suffix (possibly empty) of the remaining elements after dropping elements that satisfy the given predicate.

>>> dropWhile (<3) $ slist [1..10]
Slist {sList = [3,4,5,6,7,8,9,10], sSize = Size 8}
>>> dropWhile (<=10) $ slist [1..10]
Slist {sList = [], sSize = Size 0}
>>> dropWhile (<0) $ slist [1..10]
Slist {sList = [1,2,3,4,5,6,7,8,9,10], sSize = Size 10}
>>> take 5 $ dropWhile (<3) $ infiniteSlist [1..]
Slist {sList = [3,4,5,6,7], sSize = Size 5}
>> dropWhile (< 5) $ infiniteSlist [1..]
Slist {sList = [5,6..], sSize = Infinity}

span :: forall a. (a -> Bool) -> Slist a -> (Slist a, Slist a) Source #

O(n). Returns a tuple where first element is longest prefix (possibly empty) of the slist of elements that satisfy the given predicate and second element is the remainder of the list.

>>> span (<3) $ slist [1,2,3,4,1,2,3,4]
(Slist {sList = [1,2], sSize = Size 2},Slist {sList = [3,4,1,2,3,4], sSize = Size 6})
>>> span (<=10) $ slist [1..3]
(Slist {sList = [1,2,3], sSize = Size 3},Slist {sList = [], sSize = Size 0})
>>> span (<0) $ slist [1..3]
(Slist {sList = [], sSize = Size 0},Slist {sList = [1,2,3], sSize = Size 3})
>> span (<3) $ infiniteSlist [1..]
(Slist {sList = [1,2], sSize = Size 2}, Slist {sList = [3..], sSize = Infinity})

break :: (a -> Bool) -> Slist a -> (Slist a, Slist a) Source #

O(n). Returns a tuple where first element is longest prefix (possibly empty) of the slist of elements that do not satisfy the given predicate and second element is the remainder of the list.

> break p = span (not . p)

stripPrefix :: Eq a => Slist a -> Slist a -> Maybe (Slist a) Source #

O(m). Drops the given prefix from a list. It returns Nothing if the slist did not start with the given prefix, or Just the slist after the prefix, if it does.

>>> stripPrefix (slist "foo") (slist "foobar")
Just (Slist {sList = "bar", sSize = Size 3})
>>> stripPrefix (slist "foo") (slist "foo")
Just (Slist {sList = "", sSize = Size 0})
>>> stripPrefix (slist "foo") (slist "barfoo")
Nothing
>>> stripPrefix mempty  (slist "foo")
Just (Slist {sList = "foo", sSize = Size 3})
>>> stripPrefix (infiniteSlist [0..]) (infiniteSlist [1..])
Nothing

Note: this function could hang on the infinite slists.

>> stripPrefix (infiniteSlist [1..]) (infiniteSlist [1..])
<hangs>

Use safeStripPrefix instead.

safeStripPrefix :: Eq a => Slist a -> Slist a -> Maybe (Slist a) Source #

Similar to stripPrefix, but never hangs on infinite lists and returns Nothing in that case.

>>> safeStripPrefix (infiniteSlist [1..]) (infiniteSlist [1..])
Nothing
>>> safeStripPrefix (infiniteSlist [0..]) (infiniteSlist [1..])
Nothing

group :: Eq a => Slist a -> Slist (Slist a) Source #

O(n). Takes a slist and returns a slist of slists such that the concatenation of the result is equal to the argument. Moreover, each sublist in the result contains only equal elements.

It is a special case of groupBy, which allows to supply their own equality test.

>>> group $ slist "Mississippi"
Slist {sList = [Slist {sList = "M", sSize = Size 1},Slist {sList = "i", sSize = Size 1},Slist {sList = "ss", sSize = Size 2},Slist {sList = "i", sSize = Size 1},Slist {sList = "ss", sSize = Size 2},Slist {sList = "i", sSize = Size 1},Slist {sList = "pp", sSize = Size 2},Slist {sList = "i", sSize = Size 1}], sSize = Size 8}
>>> group mempty
Slist {sList = [], sSize = Size 0}

groupBy :: (a -> a -> Bool) -> Slist a -> Slist (Slist a) Source #

O(n). Non-overloaded version of the group function.

>>> groupBy (>) $ slist "Mississippi"
Slist {sList = [Slist {sList = "M", sSize = Size 1},Slist {sList = "i", sSize = Size 1},Slist {sList = "s", sSize = Size 1},Slist {sList = "si", sSize = Size 2},Slist {sList = "s", sSize = Size 1},Slist {sList = "sippi", sSize = Size 5}], sSize = Size 6}

inits :: Slist a -> Slist (Slist a) Source #

O(n). Returns all initial segments of the argument, shortest first.

>>> inits $ slist "abc"
Slist {sList = [Slist {sList = "", sSize = Size 0},Slist {sList = "a", sSize = Size 1},Slist {sList = "ab", sSize = Size 2},Slist {sList = "abc", sSize = Size 3}], sSize = Size 4}
>>> inits mempty
Slist {sList = [Slist {sList = [], sSize = Size 0}], sSize = Size 1}

tails :: Slist a -> Slist (Slist a) Source #

O(n). Returns all final segments of the argument, shortest first.

>>> tails $ slist "abc"
Slist {sList = [Slist {sList = "abc", sSize = Size 3},Slist {sList = "bc", sSize = Size 2},Slist {sList = "c", sSize = Size 1},Slist {sList = "", sSize = Size 0}], sSize = Size 4}
>>> tails mempty
Slist {sList = [Slist {sList = [], sSize = Size 0}], sSize = Size 1}

Predicates

isPrefixOf :: Eq a => Slist a -> Slist a -> Bool Source #

O(m). Takes two slists and returns True iff the first slist is a prefix of the second.

>>> isPrefixOf (slist "Hello") (slist "Hello World!")
True
>>> isPrefixOf (slist "Hello World!") (slist "Hello")
False
>>> isPrefixOf mempty (slist "hey")
True

Note: this function could hang on the infinite slists.

>> isPrefixOf (infiniteSlist [1..]) (infiniteSlist [1..])
<hangs>

Use safeIsPrefixOf instead.

safeIsPrefixOf :: Eq a => Slist a -> Slist a -> Bool Source #

Similar to isPrefixOf, but never hangs on infinite lists and returns False in that case.

>>> safeIsPrefixOf (infiniteSlist [1..]) (infiniteSlist [1..])
False
>>> safeIsPrefixOf (infiniteSlist [0..]) (infiniteSlist [1..])
False

isSuffixOf :: Eq a => Slist a -> Slist a -> Bool Source #

Takes two slists and returns True iff the first slist is a suffix of the second.

>>> isSuffixOf (slist "World!") (slist "Hello World!")
True
>>> isSuffixOf (slist "Hello World!") (slist "Hello")
False
>>> isSuffixOf mempty (slist "hey")
True

Note: this function hangs if the second slist is infinite.

>> isSuffixOf anything (infiniteSlist [1..])
<hangs>

Use safeIsSuffixOf instead.

safeIsSuffixOf :: Eq a => Slist a -> Slist a -> Bool Source #

Similar to isSuffixOf, but never hangs on infinite lists and returns False in that case.

>>> safeIsSuffixOf (slist [1,2]) (infiniteSlist [1..])
False
>>> safeIsSuffixOf (infiniteSlist [1..]) (infiniteSlist [1..])
False

isInfixOf :: Eq a => Slist a -> Slist a -> Bool Source #

Takes two slists and returns True iff the first slist is contained, wholly and intact, anywhere within the second.

>>> isInfixOf (slist "ll") (slist "Hello World!")
True
>>> isInfixOf (slist " Hello") (slist "Hello")
False
>>> isInfixOf (slist "Hello World!") (slist "Hello")
False

Note: this function could hang on the infinite slists.

>> isPrefixOf (infiniteSlist [1..]) (infiniteSlist [1..])
<hangs>

Use safeIsInfixOf instead.

safeIsInfixOf :: Eq a => Slist a -> Slist a -> Bool Source #

Similar to isInfixOf, but never hangs on infinite lists and returns False in that case.

>>> safeIsInfixOf (infiniteSlist [1..]) (infiniteSlist [1..])
False
>>> safeIsInfixOf (infiniteSlist [0..]) (infiniteSlist [1..])
False

isSubsequenceOf :: Eq a => Slist a -> Slist a -> Bool Source #

Takes two slists and returns True if all the elements of the first slist occur, in order, in the second. The elements do not have to occur consecutively.

isSubsequenceOf x y is equivalent to elem x (subsequences y).

>>> isSubsequenceOf (slist "Hll") (slist "Hello World!")
True
>>> isSubsequenceOf (slist "") (slist "Hello World!")
True
>>> isSubsequenceOf (slist "Hallo") (slist "Hello World!")
False

Note: this function hangs if the second slist is infinite.

>> isSuffixOf anything (infiniteSlist [1..])
<hangs>

Use safeIsSuffixOf instead.

safeIsSubsequenceOf :: Eq a => Slist a -> Slist a -> Bool Source #

Similar to isSubsequenceOf, but never hangs on infinite lists and returns False in that case.

>>> safeIsSubsequenceOf (infiniteSlist [1..]) (infiniteSlist [1..])
False
>>> safeIsSubsequenceOf (infiniteSlist [0..]) (infiniteSlist [1..])
False

Searching

Searching by equality

lookup :: Eq a => a -> Slist (a, b) -> Maybe b Source #

O(n). Looks up by the given key in the slist of key-value pairs.

>>> lookup 42 $ slist $ [(1, "one"), (2, "two")]
Nothing
>>> lookup 42 $ slist $ [(1, "one"), (2, "two"), (42, "life, the universe and everything")]
Just "life, the universe and everything"
>>> lookup 1 $ zip (infiniteSlist  [1..]) (infiniteSlist [0..])
Just 0

Searching with a predicate

filter :: forall a. (a -> Bool) -> Slist a -> Slist a Source #

O(n). Returns the slist of the elements that satisfy the given predicate.

>>> filter (<3) $ slist [1..5]
Slist {sList = [1,2], sSize = Size 2}
>>> take 5 $ filter odd $ infiniteSlist [1..]
Slist {sList = [1,3,5,7,9], sSize = Size 5}

partition :: forall a. (a -> Bool) -> Slist a -> (Slist a, Slist a) Source #

O(n). Returns the pair of slists of elements which do and do not satisfy the given predicate.

>>> partition (<3) $ slist [1..5]
(Slist {sList = [1,2], sSize = Size 2},Slist {sList = [3,4,5], sSize = Size 3})

Indexing

at :: Int -> Slist a -> Maybe a Source #

O(i) | i < n and O(1) | otherwise.

Returns the element of the slist at the given position. If the i exceeds the length of the slist the function returns Nothing.

>>> let sl = slist [1..10]
>>> at 0 sl
Just 1
>>> at (-1) sl
Nothing
>>> at 11 sl
Nothing
>>> at 9 sl
Just 10

unsafeAt :: Int -> Slist a -> a Source #

O(min i n). Unsafe version of the at function. If the element on the given position does not exist it throws the exception at run-time.

>>> let sl = slist [1..10]
>>> unsafeAt 0 sl
1
>>> unsafeAt (-1) sl
*** Exception: Prelude.!!: negative index
>>> unsafeAt 11 sl
*** Exception: Prelude.!!: index too large
>>> unsafeAt 9 sl
10

elemIndex :: Eq a => a -> Slist a -> Maybe Int Source #

O(n). Returns the index of the first element in the given slist which is equal (by ==) to the query element, or Nothing if there is no such element.

>>> elemIndex 5 $ slist [1..10]
Just 4
>>> elemIndex 0 $ slist [1..10]
Nothing

elemIndices :: Eq a => a -> Slist a -> Slist Int Source #

O(n). Extends elemIndex, by returning the indices of all elements equal to the query element, in ascending order.

>>> elemIndices 1 $ slist [1,1,1,2,2,4,5,1,9,1]
Slist {sList = [0,1,2,7,9], sSize = Size 5}
>>> take 5 $ elemIndices 1 $ repeat 1
Slist {sList = [0,1,2,3,4], sSize = Size 5}

findIndex :: (a -> Bool) -> Slist a -> Maybe Int Source #

O(n). Returns the index of the first element in the slist satisfying the given predicate, or Nothing if there is no such element.

>>> findIndex (>3) $ slist [1..5]
Just 3
>>> findIndex (<0) $ slist [1..5]
Nothing

findIndices :: forall a. (a -> Bool) -> Slist a -> Slist Int Source #

O(n). Extends findIndex, by returning the indices of all elements satisfying the given predicate, in ascending order.

>>> findIndices (<3) $ slist [1..5]
Slist {sList = [0,1], sSize = Size 2}
>>> findIndices (<0) $ slist [1..5]
Slist {sList = [], sSize = Size 0}
>>> take 5 $ findIndices (<=10) $ infiniteSlist [1..]
Slist {sList = [0,1,2,3,4], sSize = Size 5}

Zipping and unzipping

zip :: Slist a -> Slist b -> Slist (a, b) Source #

O(min n m). Takes two slists and returns a slist of corresponding pairs.

>>> zip (slist [1,2]) (slist ["one", "two"])
Slist {sList = [(1,"one"),(2,"two")], sSize = Size 2}
>>> zip (slist [1,2,3]) (slist ["one", "two"])
Slist {sList = [(1,"one"),(2,"two")], sSize = Size 2}
>>> zip (slist [1,2]) (slist ["one", "two", "three"])
Slist {sList = [(1,"one"),(2,"two")], sSize = Size 2}
>>> zip mempty (slist [1..5])
Slist {sList = [], sSize = Size 0}
>>> zip (infiniteSlist [1..]) (slist ["one", "two"])
Slist {sList = [(1,"one"),(2,"two")], sSize = Size 2}

zip3 :: Slist a -> Slist b -> Slist c -> Slist (a, b, c) Source #

O(minimum [n1, n2, n3]). Takes three slists and returns a slist of triples, analogous to zip.

zipWith :: (a -> b -> c) -> Slist a -> Slist b -> Slist c Source #

O(min n m). Generalises zip by zipping with the given function, instead of a tupling function.

For example, zipWith (+) is applied to two lists to produce the list of corresponding sums.

zipWith3 :: (a -> b -> c -> d) -> Slist a -> Slist b -> Slist c -> Slist d Source #

O(minimum [n1, n2, n3]). Takes a function which combines three elements, as well as three slists and returns a slist of their point-wise combination, analogous to zipWith.

unzip :: Slist (a, b) -> (Slist a, Slist b) Source #

O(n). Transforms a slist of pairs into a slist of first components and a slist of second components.

>>> unzip $ slist [(1,"one"),(2,"two")]
(Slist {sList = [1,2], sSize = Size 2},Slist {sList = ["one","two"], sSize = Size 2})

unzip3 :: Slist (a, b, c) -> (Slist a, Slist b, Slist c) Source #

O(n). Takes a slist of triples and returns three slists, analogous to unzip.

Sets

Set is a special case of slists so that it consist of the unique elements.

Example of set:

Slist {sList = "qwerty", sSize = Size 6}
Slist {sList = [1..], sSize = Infinity}

nub :: Eq a => Slist a -> Slist a Source #

O(n^2). Removes duplicate elements from a slist. In particular, it keeps only the first occurrence of each element.

It is a special case of nubBy, which allows to supply your own equality test.

>>> nub $ replicate 5 'a'
Slist {sList = "a", sSize = Size 1}
>>> nub mempty
Slist {sList = [], sSize = Size 0}
>>> nub $ slist [1,2,3,4,3,2,1,2,4,3,5]
Slist {sList = [1,2,3,4,5], sSize = Size 5}

nubBy :: forall a. (a -> a -> Bool) -> Slist a -> Slist a Source #

O(n^2). Behaves just like nub, except it uses a user-supplied equality predicate instead of the overloaded == function.

>>> nubBy (\x y -> mod x 3 == mod y 3) $ slist [1,2,4,5,6]
Slist {sList = [1,2,6], sSize = Size 3}

delete :: Eq a => a -> Slist a -> Slist a Source #

O(n). Removes the first occurrence of the given element from its slist argument.

>>> delete 'h' $ slist "hahaha"
Slist {sList = "ahaha", sSize = Size 5}
>>> delete 0 $ slist [1..3]
Slist {sList = [1,2,3], sSize = Size 3}

deleteBy :: forall a. (a -> a -> Bool) -> a -> Slist a -> Slist a Source #

O(n). Behaves like delete, but takes a user-supplied equality predicate.

>>> deleteBy (>=) 4 $ slist [1..10]
Slist {sList = [2,3,4,5,6,7,8,9,10], sSize = Size 9}

deleteFirstsBy :: (a -> a -> Bool) -> Slist a -> Slist a -> Slist a Source #

O(n*m). Takes a predicate and two slists and returns the first slist with the first occurrence of each element of the second slist removed.

>>> deleteFirstsBy (==) (slist [1..5]) (slist [2,8,4,10,1])
Slist {sList = [3,5], sSize = Size 2}

diff :: Eq a => Slist a -> Slist a -> Slist a Source #

O(n*m). Returns the difference between two slists. The operation is non-associative. In the result of diff xs ys, the first occurrence of each element of ys in turn (if any) has been removed from xs. Thus

diff (xs <> ys) ys == xs
>>> diff (slist [1..10]) (slist [1,3..10])
Slist {sList = [2,4,6,8,10], sSize = Size 5}
>>> diff (slist [1,3..10]) (slist [2,4..10])
Slist {sList = [1,3,5,7,9], sSize = Size 5}

union :: Eq a => Slist a -> Slist a -> Slist a Source #

O(n*m). Returns the list union of the two slists.

>>> union (slist "pen") (slist "apple")
Slist {sList = "penal", sSize = Size 5}

Duplicates, and elements of the first slist, are removed from the the second slist, but if the first slist contains duplicates, so will the result.

>>> union (slist "apple") (slist "pen")
Slist {sList = "applen", sSize = Size 6}

It is a special case of unionBy.

unionBy :: (a -> a -> Bool) -> Slist a -> Slist a -> Slist a Source #

O(n*m). Non-overloaded version of union.

intersect :: Eq a => Slist a -> Slist a -> Slist a Source #

O(n*m). Returns the slist intersection of two slists.

>>> intersect (slist [1,2,3,4]) (slist [2,4,6,8])
Slist {sList = [2,4], sSize = Size 2}

If the first list contains duplicates, so will the result.

>>> intersect (slist [1,2,2,3,4]) (slist [6,4,4,2])
Slist {sList = [2,2,4], sSize = Size 3}

If the first slist is infinite, so will be the result.

If the element is found in both the first and the second slist, the element from the first slist will be used.

It is a special case of intersectBy.

intersectBy :: forall a. (a -> a -> Bool) -> Slist a -> Slist a -> Slist a Source #

O(n*m). Non-overloaded version of intersect.

Ordered slists

sort :: Ord a => Slist a -> Slist a Source #

O(n log n). implements a stable sorting algorithm. It is a special case of sortBy.

Elements are arranged from from lowest to highest, keeping duplicates in the order they appeared in the input.

>>> sort $ slist [10, 9..1]
Slist {sList = [1,2,3,4,5,6,7,8,9,10], sSize = Size 10}

Note: this function hangs on infinite slists.

sortBy :: (a -> a -> Ordering) -> Slist a -> Slist a Source #

O(n log n). Non-overloaded version of sort.

>>> sortBy (\(a,_) (b,_) -> compare a b) $ slist [(2, "world"), (4, "!"), (1, "Hello")]
Slist {sList = [(1,"Hello"),(2,"world"),(4,"!")], sSize = Size 3}

Note: this function hangs on infinite slists.

sortOn :: Ord b => (a -> b) -> Slist a -> Slist a Source #

O(n log n). Sorts a list by comparing the results of a key function applied to each element. sortOn f is equivalent to sortBy (comparing f), but has the performance advantage of only evaluating f once for each element in the input list. This is called the decorate-sort-undecorate paradigm, or Schwartzian transform.

Elements are arranged from lowest to highest, keeping duplicates in the order they appeared in the input.

>>> sortOn fst $ slist [(2, "world"), (4, "!"), (1, "Hello")]
Slist {sList = [(1,"Hello"),(2,"world"),(4,"!")], sSize = Size 3}

Note: this function hangs on infinite slists.

insert :: Ord a => a -> Slist a -> Slist a Source #

O(n). Takes an element and a slist and inserts the element into the slist at the first position where it is less than or equal to the next element. In particular, if the list is sorted before the call, the result will also be sorted. It is a special case of insertBy.

>>> insert 4 $ slist [1,2,3,5,6]
Slist {sList = [1,2,3,4,5,6], sSize = Size 6}

insertBy :: (a -> a -> Ordering) -> a -> Slist a -> Slist a Source #

O(n). The non-overloaded version of insert.

Generic functions

genericLength :: Num i => Slist a -> i Source #

O(1). The genericLength function is an overloaded version of length. In particular, instead of returning an Int, it returns any type which is an instance of Num.

>>> genericLength $ one 42
1
>>> genericLength $ slist [1..3]
3
>>> genericLength $ infiniteSlist [1..]
9223372036854775807

genericTake :: Integral i => i -> Slist a -> Slist a Source #

O(i) | i < n and O(1) | otherwise. The genericTake function is an overloaded version of take, which accepts any Integral value as the number of elements to take.

>>> genericTake 5 $ slist "Hello world!"
Slist {sList = "Hello", sSize = Size 5}
>>> genericTake 20 $ slist "small"
Slist {sList = "small", sSize = Size 5}
>>> genericTake 0 $ slist "none"
Slist {sList = "", sSize = Size 0}
>>> genericTake (-11) $ slist "hmm"
Slist {sList = "", sSize = Size 0}
>>> genericTake 4 $ infiniteSlist [1..]
Slist {sList = [1,2,3,4], sSize = Size 4}

genericDrop :: Integral i => i -> Slist a -> Slist a Source #

O(i) | i < n and O(1) | otherwise. The genericDrop function is an overloaded version of drop, which accepts any Integral value as the number of elements to drop.

>>> genericDrop 6 $ slist "Hello World"
Slist {sList = "World", sSize = Size 5}
>>> genericDrop 42 $ slist "oops!"
Slist {sList = "", sSize = Size 0}
>>> genericDrop 0 $ slist "Hello World!"
Slist {sList = "Hello World!", sSize = Size 12}
>>> genericDrop (-4) $ one 42
Slist {sList = [42], sSize = Size 1}
>> drop 5 $ infiniteSlist [1..]
Slist {sList = [6..], sSize = Infinity}

genericSplitAt :: Integral i => i -> Slist a -> (Slist a, Slist a) Source #

O(i) | i < n and O(1) | otherwise. The genericSplitAt function is an overloaded version of splitAt, which accepts any Integral value as the position at which to split.

>>> genericSplitAt 5 $ slist "Hello World!"
(Slist {sList = "Hello", sSize = Size 5},Slist {sList = " World!", sSize = Size 7})
>>> genericSplitAt 0 $ slist "abc"
(Slist {sList = "", sSize = Size 0},Slist {sList = "abc", sSize = Size 3})
>>> genericSplitAt 4 $ slist "abc"
(Slist {sList = "abc", sSize = Size 3},Slist {sList = "", sSize = Size 0})
>>> genericSplitAt (-42) $ slist "??"
(Slist {sList = "", sSize = Size 0},Slist {sList = "??", sSize = Size 2})
>> genericSplitAt 2 $ infiniteSlist [1..]
(Slist {sList = [1,2], sSize = Size 2}, Slist {sList = [3..], sSize = Infinity})

genericAt :: Integral i => i -> Slist a -> Maybe a Source #

O(i) | i < n and O(1) | otherwise. The genericAt function is an overloaded version of at, which accepts any Integral value as the position. If the element on the given position does not exist it will return Nothing.

>>> let sl = slist [1..10]
>>> genericAt 0 sl
Just 1
>>> genericAt (-1) sl
Nothing
>>> genericAt 11 sl
Nothing
>>> genericAt 9 sl
Just 10

genericUnsafeAt :: Integral i => i -> Slist a -> a Source #

O(min i n). The genericUnsafeAt function is an overloaded version of unsafeAt, which accepts any Integral value as the position. If the element on the given position does not exist it throws the exception at run-time.

>>> let sl = slist [1..10]
>>> genericUnsafeAt 0 sl
1
>>> genericUnsafeAt (-1) sl
*** Exception: Slist.genericUnsafeAt: negative argument
>>> genericUnsafeAt 11 sl
*** Exception: Slist.genericUnsafeAt: index too large
>>> genericUnsafeAt 9 sl
10

genericReplicate :: Integral i => i -> a -> Slist a Source #

O(n). The genericReplicate function is an overloaded version of replicate, which accepts any Integral value as the number of repetitions to make.

>>> genericReplicate 3 'o'
Slist {sList = "ooo", sSize = Size 3}
>>> genericReplicate (-11) "hmm"
Slist {sList = [], sSize = Size 0}