mono-traversable-0.10.1: Type classes for mapping, folding, and traversing monomorphic containers

Safe HaskellNone
LanguageHaskell2010

Data.Sequences

Description

Warning: This module should be considered highly experimental.

Synopsis

Documentation

class (Integral (Index seq), GrowingAppend seq) => SemiSequence seq where Source

SemiSequence was created to share code between IsSequence and MinLen.

Semi means SemiGroup A SemiSequence can accomodate a SemiGroup such as NonEmpty or MinLen A Monoid should be able to fill out IsSequence.

SemiSequence operations maintain the same type because they all maintain the same number of elements or increase them. However, a decreasing function such as filter may change they type. For example, from NonEmpty to '[]' This type-changing function exists on NonNull as nfilter

filter and other such functions are placed in IsSequence

Associated Types

type Index seq Source

The type of the index of a sequence.

Methods

intersperse :: Element seq -> seq -> seq Source

intersperse takes an element and intersperses that element between the elements of the sequence.

> intersperse ',' "abcde"
"a,b,c,d,e"

reverse :: seq -> seq Source

Reverse a sequence

> reverse "hello world"
"dlrow olleh"

find :: (Element seq -> Bool) -> seq -> Maybe (Element seq) Source

find takes a predicate and a sequence and returns the first element in the sequence matching the predicate, or Nothing if there isn't an element that matches the predicate.

> find (== 5) [1 .. 10]
Just 5

> find (== 15) [1 .. 10]
Nothing

sortBy :: (Element seq -> Element seq -> Ordering) -> seq -> seq Source

Sort a sequence using an supplied element ordering function.

> let compare' x y = case compare x y of LT -> GT; EQ -> EQ; GT -> LT
> sortBy compare' [5,3,6,1,2,4]
[6,5,4,3,2,1]

cons :: Element seq -> seq -> seq Source

Prepend an element onto a sequence.

> 4 `cons` [1,2,3]
[4,1,2,3]

snoc :: seq -> Element seq -> seq Source

Append an element onto a sequence.

> [1,2,3] `snoc` 4
[1,2,3,4]

singleton :: IsSequence seq => Element seq -> seq Source

Create a sequence from a single element.

> singleton a :: String
"a"
> singleton a :: Vector Char
fromList "a"

class (Monoid seq, MonoTraversable seq, SemiSequence seq, MonoPointed seq) => IsSequence seq where Source

Sequence Laws:

fromList . otoList = id
fromList (x <> y) = fromList x <> fromList y
otoList (fromList x <> fromList y) = x <> y

Minimal complete definition

Nothing

Methods

fromList :: [Element seq] -> seq Source

Convert a list to a sequence.

> fromList [a, b, c] :: Text
"abc"

break :: (Element seq -> Bool) -> seq -> (seq, seq) Source

break applies a predicate to a sequence, and returns a tuple where the first element is the longest prefix (possibly empty) of elements that do not satisfy the predicate. The second element of the tuple is the remainder of the sequence.

break p is equivalent to span (not . p)

> break (> 3) (fromList [1,2,3,4,1,2,3,4] :: Vector Int)
(fromList [1,2,3],fromList [4,1,2,3,4])

> break (< z) (fromList "abc" :: Text)
("","abc")

> break (> z) (fromList "abc" :: Text)
("abc","")

span :: (Element seq -> Bool) -> seq -> (seq, seq) Source

span applies a predicate to a sequence, and returns a tuple where the first element is the longest prefix (possibly empty) that does satisfy the predicate. The second element of the tuple is the remainder of the sequence.

span p xs is equivalent to (takeWhile p xs, dropWhile p xs)

> span (< 3) (fromList [1,2,3,4,1,2,3,4] :: Vector Int)
(fromList [1,2],fromList [3,4,1,2,3,4])

> span (< z) (fromList "abc" :: Text)
("abc","")

> span (< 0) 1,2,3

dropWhile :: (Element seq -> Bool) -> seq -> seq Source

dropWhile returns the suffix remaining after takeWhile.

> dropWhile (< 3) [1,2,3,4,5,1,2,3]
[3,4,5,1,2,3]

> dropWhile (< z) (fromList "abc" :: Text)
""

takeWhile :: (Element seq -> Bool) -> seq -> seq Source

takeWhile applies a predicate to a sequence, and returns the longest prefix (possibly empty) of the sequence of elements that satisfy the predicate.

> takeWhile (< 3) [1,2,3,4,5,1,2,3]
[1,2]

> takeWhile (< z) (fromList "abc" :: Text)
"abc"

splitAt :: Index seq -> seq -> (seq, seq) Source

splitAt n se returns a tuple where the first element is the prefix of the sequence se with length n, and the second element is the remainder of the sequence.

> splitAt 6 "Hello world!"
("Hello ","world!")

> splitAt 3 (fromList [1,2,3,4,5] :: Vector Int)
(fromList [1,2,3],fromList [4,5])

unsafeSplitAt :: Index seq -> seq -> (seq, seq) Source

Equivalent to splitAt.

take :: Index seq -> seq -> seq Source

take n returns the prefix of a sequence of length n, or the sequence itself if n > olength seq.

> take 3 "abcdefg"
"abc"
> take 4 (fromList [1,2,3,4,5,6] :: Vector Int)
fromList [1,2,3,4]

unsafeTake :: Index seq -> seq -> seq Source

Equivalent to take.

drop :: Index seq -> seq -> seq Source

drop n returns the suffix of a sequence after the first n elements, or an empty sequence if n > olength seq.

> drop 3 "abcdefg"
"defg"
> drop 4 (fromList [1,2,3,4,5,6] :: Vector Int)
fromList [5,6]

unsafeDrop :: Index seq -> seq -> seq Source

Equivalent to drop

partition :: (Element seq -> Bool) -> seq -> (seq, seq) Source

partition takes a predicate and a sequence and returns the pair of sequences of elements which do and do not satisfy the predicate.

partition p se = (filter p se, filter (not . p) se)

uncons :: seq -> Maybe (Element seq, seq) Source

uncons returns the tuple of the first element of a sequence and the rest of the sequence, or Nothing if the sequence is empty.

> uncons (fromList [1,2,3,4] :: Vector Int)
Just (1,fromList [2,3,4])

> uncons ([] :: [Int])
Nothing

unsnoc :: seq -> Maybe (seq, Element seq) Source

unsnoc returns the tuple of the init of a sequence and the last element, or Nothing if the sequence is empty.

> uncons (fromList [1,2,3,4] :: Vector Int)
Just (fromList [1,2,3],4)

> uncons ([] :: [Int])
Nothing

filter :: (Element seq -> Bool) -> seq -> seq Source

filter given a predicate returns a sequence of all elements that satisfy the predicate.

> filter (< 5) [1 .. 10]
[1,2,3,4]

filterM :: Monad m => (Element seq -> m Bool) -> seq -> m seq Source

The monadic version of filter.

replicate :: Index seq -> Element seq -> seq Source

replicate n x is a sequence of length n with x as the value of every element.

> replicate 10 a :: Text
"aaaaaaaaaa"

replicateM :: Monad m => Index seq -> m (Element seq) -> m seq Source

The monadic version of replicateM.

groupBy :: (Element seq -> Element seq -> Bool) -> seq -> [seq] Source

group takes a sequence and returns a list of sequences such that the concatenation of the result is equal to the argument. Each subsequence in the result contains only equal elements, using the supplied equality test.

> groupBy (==) Mississippi
[M,"i","ss","i","ss","i","pp","i"]

groupAllOn :: Eq b => (Element seq -> b) -> seq -> [seq] Source

Similar to standard groupBy, but operates on the whole collection, not just the consecutive items.

subsequences :: seq -> [seq] Source

subsequences returns a list of all subsequences of the argument.

> subsequences "abc"
["","a","b","ab","c","ac","bc","abc"]

permutations :: seq -> [seq] Source

permutations returns a list of all permutations of the argument.

> permutations "abc"
["abc","bac","cba","bca","cab","acb"]

tailEx :: seq -> seq Source

Unsafe

Get the tail of a sequence, throw an exception if the sequence is empty.

> tailEx [1,2,3]
[2,3]

initEx :: seq -> seq Source

Unsafe

Get the init of a sequence, throw an exception if the sequence is empty.

> initEx [1,2,3]
[1,2]

unsafeTail :: seq -> seq Source

Equivalent to tailEx.

unsafeInit :: seq -> seq Source

Equivalent to initEx.

index :: seq -> Index seq -> Maybe (Element seq) Source

Get the element of a sequence at a certain index, returns Nothing if that index does not exist.

> index (fromList [1,2,3] :: Vector Int) 1
Just 2
> index (fromList [1,2,3] :: Vector Int) 4
Nothing

indexEx :: seq -> Index seq -> Element seq Source

Unsafe

Get the element of a sequence at a certain index, throws an exception if the index does not exist.

unsafeIndex :: seq -> Index seq -> Element seq Source

Equivalent to indexEx.

intercalate :: seq -> [seq] -> seq Source

intercalate seq seqs inserts seq in between seqs and concatenates the result.

Since 0.9.3

splitWhen :: (Element seq -> Bool) -> seq -> [seq] Source

splitWhen splits a sequence into components delimited by separators, where the predicate returns True for a separator element. The resulting components do not contain the separators. Two adjacent separators result in an empty component in the output. The number of resulting components is greater by one than number of separators.

Since 0.9.3

defaultFind :: MonoFoldable seq => (Element seq -> Bool) -> seq -> Maybe (Element seq) Source

Use Data.List's implementation of find.

defaultIntersperse :: IsSequence seq => Element seq -> seq -> seq Source

Use Data.List's implementation of intersperse.

defaultReverse :: IsSequence seq => seq -> seq Source

Use Data.List's implementation of reverse.

defaultSortBy :: IsSequence seq => (Element seq -> Element seq -> Ordering) -> seq -> seq Source

Use Data.List's implementation of sortBy.

defaultIntercalate :: IsSequence seq => seq -> [seq] -> seq Source

Default intercalate

defaultSplitWhen :: IsSequence seq => (Element seq -> Bool) -> seq -> [seq] Source

vectorSortBy :: Vector v e => (e -> e -> Ordering) -> v e -> v e Source

Sort a vector using an supplied element ordering function.

vectorSort :: (Vector v e, Ord e) => v e -> v e Source

Sort a vector.

defaultCons :: IsSequence seq => Element seq -> seq -> seq Source

Use Data.List's : to prepend an element to a sequence.

defaultSnoc :: IsSequence seq => seq -> Element seq -> seq Source

Use Data.List's ++ to append an element to a sequence.

tailDef :: IsSequence seq => seq -> seq Source

like Data.List.tail, but an input of mempty returns mempty

initDef :: IsSequence seq => seq -> seq Source

like Data.List.init, but an input of mempty returns mempty

class (MonoFoldableEq seq, IsSequence seq, Eq (Element seq)) => EqSequence seq where Source

A typeclass for sequences whose elements have the Eq typeclass

Minimal complete definition

Nothing

Methods

splitElem :: Element seq -> seq -> [seq] Source

splitElem splits a sequence into components delimited by separator element. It's equivalent to splitWhen with equality predicate:

splitElem sep === splitWhen (== sep)

Since 0.9.3

splitSeq :: seq -> seq -> [seq] Source

splitSeq splits a sequence into components delimited by separator subsequence. splitSeq is the right inverse of intercalate:

intercalate x . splitSeq x === id

splitElem can be considered a special case of splitSeq

splitSeq (singleton sep) === splitElem sep

splitSeq mempty is another special case: it splits just before each element, and in line with splitWhen rules, it has at least one output component:

> splitSeq "" ""
[""]
> splitSeq "" "a"
["", "a"]
> splitSeq "" "ab"
["", "a", "b"]

Since 0.9.3

stripPrefix :: seq -> seq -> Maybe seq Source

stripPrefix drops the given prefix from a sequence. It returns Nothing if the sequence did not start with the prefix given, or Just the sequence after the prefix, if it does.

> stripPrefix "foo" "foobar"
Just "foo"
> stripPrefix "abc" "foobar"
Nothing

stripSuffix :: seq -> seq -> Maybe seq Source

stripSuffix drops the given suffix from a sequence. It returns Nothing if the sequence did not end with the suffix given, or Just the sequence before the suffix, if it does.

> stripSuffix "bar" "foobar"
Just "foo"
> stripSuffix "abc" "foobar"
Nothing

isPrefixOf :: seq -> seq -> Bool Source

isPrefixOf takes two sequences and returns True if the first sequence is a prefix of the second.

isSuffixOf :: seq -> seq -> Bool Source

isSuffixOf takes two sequences and returns True if the first sequence is a suffix of the second.

isInfixOf :: seq -> seq -> Bool Source

isInfixOf takes two sequences and returns true if the first sequence is contained, wholly and intact, anywhere within the second.

group :: seq -> [seq] Source

Equivalent to groupBy (==)

groupAll :: seq -> [seq] Source

Similar to standard group, but operates on the whole collection, not just the consecutive items.

Equivalent to groupAllOn id

elem :: EqSequence seq => Element seq -> seq -> Bool Source

Deprecated: use oelem

notElem :: EqSequence seq => Element seq -> seq -> Bool Source

Deprecated: use onotElem

defaultSplitOn :: EqSequence s => s -> s -> [s] Source

Use splitOn from Data.List.Split

class (EqSequence seq, MonoFoldableOrd seq) => OrdSequence seq where Source

A typeclass for sequences whose elements have the Ord typeclass

Minimal complete definition

Nothing

Methods

sort :: seq -> seq Source

Sort a ordered sequence.

> sort [4,3,1,2]
[1,2,3,4]

class (IsSequence t, IsString t, Element t ~ Char) => Textual t where Source

A typeclass for sequences whose elements are Chars.

Minimal complete definition

words, unwords, lines, unlines, toLower, toUpper, toCaseFold

Methods

words :: t -> [t] Source

Break up a textual sequence into a list of words, which were delimited by white space.

> words "abc  def ghi"
["abc","def","ghi"]

unwords :: [t] -> t Source

Join a list of textual sequences using seperating spaces.

> unwords ["abc","def","ghi"]
"abc def ghi"

lines :: t -> [t] Source

Break up a textual sequence at newline characters.

> lines "hello\nworld"
["hello","world"]

unlines :: [t] -> t Source

Join a list of textual sequences using newlines.

> unlines ["abc","def","ghi"]
"abc\ndef\nghi"

toLower :: t -> t Source

Convert a textual sequence to lower-case.

> toLower "HELLO WORLD"
"hello world"

toUpper :: t -> t Source

Convert a textual sequence to upper-case.

> toUpper "hello world"
"HELLO WORLD"

toCaseFold :: t -> t Source

Convert a textual sequence to folded-case.

Slightly different from toLower, see Data.Text.toCaseFold

breakWord :: t -> (t, t) Source

Split a textual sequence into two parts, split at the first space.

> breakWord "hello world"
("hello","world")

breakLine :: t -> (t, t) Source

Split a textual sequence into two parts, split at the newline.

> breakLine "abc\ndef"
("abc","def")

Instances

catMaybes :: (IsSequence (f (Maybe t)), Functor f, Element (f (Maybe t)) ~ Maybe t) => f (Maybe t) -> f t Source

Takes all of the Just values from a sequence of Maybe ts and concatenates them into an unboxed sequence of ts.

Since 0.6.2

sortOn :: (Ord o, SemiSequence seq) => (Element seq -> o) -> seq -> seq Source

Same as sortBy . comparing.

Since 0.7.0