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

Safe HaskellNone
LanguageHaskell2010

Data.Sequences

Description

Abstractions over sequential data structures, like lists and vectors.

Synopsis

Documentation

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

SemiSequence was created to share code between IsSequence and NonNull.

Semi means SemiGroup A SemiSequence can accomodate a SemiGroup such as NonEmpty or NonNull 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

NOTE: Like GrowingAppend, ideally we'd have a Semigroup superclass constraint here, but that would pull in more dependencies to this package than desired.

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]
Instances
SemiSequence ByteString Source # 
Instance details

Defined in Data.Sequences

Associated Types

type Index ByteString :: Type Source #

SemiSequence ByteString Source # 
Instance details

Defined in Data.Sequences

Associated Types

type Index ByteString :: Type Source #

SemiSequence Text Source # 
Instance details

Defined in Data.Sequences

Associated Types

type Index Text :: Type Source #

SemiSequence Text Source # 
Instance details

Defined in Data.Sequences

Associated Types

type Index Text :: Type Source #

SemiSequence [a] Source # 
Instance details

Defined in Data.Sequences

Associated Types

type Index [a] :: Type Source #

Methods

intersperse :: Element [a] -> [a] -> [a] Source #

reverse :: [a] -> [a] Source #

find :: (Element [a] -> Bool) -> [a] -> Maybe (Element [a]) Source #

sortBy :: (Element [a] -> Element [a] -> Ordering) -> [a] -> [a] Source #

cons :: Element [a] -> [a] -> [a] Source #

snoc :: [a] -> Element [a] -> [a] Source #

SemiSequence (NonEmpty a) Source # 
Instance details

Defined in Data.Sequences

Associated Types

type Index (NonEmpty a) :: Type Source #

SemiSequence (Seq a) Source # 
Instance details

Defined in Data.Sequences

Associated Types

type Index (Seq a) :: Type Source #

Methods

intersperse :: Element (Seq a) -> Seq a -> Seq a Source #

reverse :: Seq a -> Seq a Source #

find :: (Element (Seq a) -> Bool) -> Seq a -> Maybe (Element (Seq a)) Source #

sortBy :: (Element (Seq a) -> Element (Seq a) -> Ordering) -> Seq a -> Seq a Source #

cons :: Element (Seq a) -> Seq a -> Seq a Source #

snoc :: Seq a -> Element (Seq a) -> Seq a Source #

Unbox a => SemiSequence (Vector a) Source # 
Instance details

Defined in Data.Sequences

Associated Types

type Index (Vector a) :: Type Source #

Storable a => SemiSequence (Vector a) Source # 
Instance details

Defined in Data.Sequences

Associated Types

type Index (Vector a) :: Type Source #

SemiSequence (Vector a) Source # 
Instance details

Defined in Data.Sequences

Associated Types

type Index (Vector a) :: Type Source #

SemiSequence seq => SemiSequence (NonNull seq) Source # 
Instance details

Defined in Data.NonNull

Associated Types

type Index (NonNull seq) :: Type Source #

Methods

intersperse :: Element (NonNull seq) -> NonNull seq -> NonNull seq Source #

reverse :: NonNull seq -> NonNull seq Source #

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

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

cons :: Element (NonNull seq) -> NonNull seq -> NonNull seq Source #

snoc :: NonNull seq -> Element (NonNull seq) -> NonNull seq Source #

singleton :: MonoPointed 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"

lengthIndex :: seq -> Index seq Source #

lengthIndex returns the length of a sequence as Index seq.

Since: 1.0.2

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

dropEnd :: Index seq -> seq -> seq Source #

Same as drop but drops from the end of the sequence instead.

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

Since: 1.0.4.0

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.

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

> unsnoc ([] :: [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]

tailMay :: seq -> Maybe seq Source #

Safe version of tailEx.

Returns Nothing instead of throwing an exception when encountering an empty monomorphic container.

Since: 1.0.0

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]

initMay :: IsSequence seq => seq -> Maybe seq Source #

Safe version of initEx.

Returns Nothing instead of throwing an exception when encountering an empty monomorphic container.

Since: 1.0.0

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.

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

Instances
IsSequence ByteString Source # 
Instance details

Defined in Data.Sequences

Methods

fromList :: [Element ByteString] -> ByteString Source #

lengthIndex :: ByteString -> Index ByteString Source #

break :: (Element ByteString -> Bool) -> ByteString -> (ByteString, ByteString) Source #

span :: (Element ByteString -> Bool) -> ByteString -> (ByteString, ByteString) Source #

dropWhile :: (Element ByteString -> Bool) -> ByteString -> ByteString Source #

takeWhile :: (Element ByteString -> Bool) -> ByteString -> ByteString Source #

splitAt :: Index ByteString -> ByteString -> (ByteString, ByteString) Source #

unsafeSplitAt :: Index ByteString -> ByteString -> (ByteString, ByteString) Source #

take :: Index ByteString -> ByteString -> ByteString Source #

unsafeTake :: Index ByteString -> ByteString -> ByteString Source #

drop :: Index ByteString -> ByteString -> ByteString Source #

unsafeDrop :: Index ByteString -> ByteString -> ByteString Source #

dropEnd :: Index ByteString -> ByteString -> ByteString Source #

partition :: (Element ByteString -> Bool) -> ByteString -> (ByteString, ByteString) Source #

uncons :: ByteString -> Maybe (Element ByteString, ByteString) Source #

unsnoc :: ByteString -> Maybe (ByteString, Element ByteString) Source #

filter :: (Element ByteString -> Bool) -> ByteString -> ByteString Source #

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

replicate :: Index ByteString -> Element ByteString -> ByteString Source #

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

groupBy :: (Element ByteString -> Element ByteString -> Bool) -> ByteString -> [ByteString] Source #

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

subsequences :: ByteString -> [ByteString] Source #

permutations :: ByteString -> [ByteString] Source #

tailEx :: ByteString -> ByteString Source #

tailMay :: ByteString -> Maybe ByteString Source #

initEx :: ByteString -> ByteString Source #

initMay :: ByteString -> Maybe ByteString Source #

unsafeTail :: ByteString -> ByteString Source #

unsafeInit :: ByteString -> ByteString Source #

index :: ByteString -> Index ByteString -> Maybe (Element ByteString) Source #

indexEx :: ByteString -> Index ByteString -> Element ByteString Source #

unsafeIndex :: ByteString -> Index ByteString -> Element ByteString Source #

splitWhen :: (Element ByteString -> Bool) -> ByteString -> [ByteString] Source #

IsSequence ByteString Source # 
Instance details

Defined in Data.Sequences

Methods

fromList :: [Element ByteString] -> ByteString Source #

lengthIndex :: ByteString -> Index ByteString Source #

break :: (Element ByteString -> Bool) -> ByteString -> (ByteString, ByteString) Source #

span :: (Element ByteString -> Bool) -> ByteString -> (ByteString, ByteString) Source #

dropWhile :: (Element ByteString -> Bool) -> ByteString -> ByteString Source #

takeWhile :: (Element ByteString -> Bool) -> ByteString -> ByteString Source #

splitAt :: Index ByteString -> ByteString -> (ByteString, ByteString) Source #

unsafeSplitAt :: Index ByteString -> ByteString -> (ByteString, ByteString) Source #

take :: Index ByteString -> ByteString -> ByteString Source #

unsafeTake :: Index ByteString -> ByteString -> ByteString Source #

drop :: Index ByteString -> ByteString -> ByteString Source #

unsafeDrop :: Index ByteString -> ByteString -> ByteString Source #

dropEnd :: Index ByteString -> ByteString -> ByteString Source #

partition :: (Element ByteString -> Bool) -> ByteString -> (ByteString, ByteString) Source #

uncons :: ByteString -> Maybe (Element ByteString, ByteString) Source #

unsnoc :: ByteString -> Maybe (ByteString, Element ByteString) Source #

filter :: (Element ByteString -> Bool) -> ByteString -> ByteString Source #

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

replicate :: Index ByteString -> Element ByteString -> ByteString Source #

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

groupBy :: (Element ByteString -> Element ByteString -> Bool) -> ByteString -> [ByteString] Source #

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

subsequences :: ByteString -> [ByteString] Source #

permutations :: ByteString -> [ByteString] Source #

tailEx :: ByteString -> ByteString Source #

tailMay :: ByteString -> Maybe ByteString Source #

initEx :: ByteString -> ByteString Source #

initMay :: ByteString -> Maybe ByteString Source #

unsafeTail :: ByteString -> ByteString Source #

unsafeInit :: ByteString -> ByteString Source #

index :: ByteString -> Index ByteString -> Maybe (Element ByteString) Source #

indexEx :: ByteString -> Index ByteString -> Element ByteString Source #

unsafeIndex :: ByteString -> Index ByteString -> Element ByteString Source #

splitWhen :: (Element ByteString -> Bool) -> ByteString -> [ByteString] Source #

IsSequence Text Source # 
Instance details

Defined in Data.Sequences

Methods

fromList :: [Element Text] -> Text Source #

lengthIndex :: Text -> Index Text Source #

break :: (Element Text -> Bool) -> Text -> (Text, Text) Source #

span :: (Element Text -> Bool) -> Text -> (Text, Text) Source #

dropWhile :: (Element Text -> Bool) -> Text -> Text Source #

takeWhile :: (Element Text -> Bool) -> Text -> Text Source #

splitAt :: Index Text -> Text -> (Text, Text) Source #

unsafeSplitAt :: Index Text -> Text -> (Text, Text) Source #

take :: Index Text -> Text -> Text Source #

unsafeTake :: Index Text -> Text -> Text Source #

drop :: Index Text -> Text -> Text Source #

unsafeDrop :: Index Text -> Text -> Text Source #

dropEnd :: Index Text -> Text -> Text Source #

partition :: (Element Text -> Bool) -> Text -> (Text, Text) Source #

uncons :: Text -> Maybe (Element Text, Text) Source #

unsnoc :: Text -> Maybe (Text, Element Text) Source #

filter :: (Element Text -> Bool) -> Text -> Text Source #

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

replicate :: Index Text -> Element Text -> Text Source #

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

groupBy :: (Element Text -> Element Text -> Bool) -> Text -> [Text] Source #

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

subsequences :: Text -> [Text] Source #

permutations :: Text -> [Text] Source #

tailEx :: Text -> Text Source #

tailMay :: Text -> Maybe Text Source #

initEx :: Text -> Text Source #

initMay :: Text -> Maybe Text Source #

unsafeTail :: Text -> Text Source #

unsafeInit :: Text -> Text Source #

index :: Text -> Index Text -> Maybe (Element Text) Source #

indexEx :: Text -> Index Text -> Element Text Source #

unsafeIndex :: Text -> Index Text -> Element Text Source #

splitWhen :: (Element Text -> Bool) -> Text -> [Text] Source #

IsSequence Text Source # 
Instance details

Defined in Data.Sequences

Methods

fromList :: [Element Text] -> Text Source #

lengthIndex :: Text -> Index Text Source #

break :: (Element Text -> Bool) -> Text -> (Text, Text) Source #

span :: (Element Text -> Bool) -> Text -> (Text, Text) Source #

dropWhile :: (Element Text -> Bool) -> Text -> Text Source #

takeWhile :: (Element Text -> Bool) -> Text -> Text Source #

splitAt :: Index Text -> Text -> (Text, Text) Source #

unsafeSplitAt :: Index Text -> Text -> (Text, Text) Source #

take :: Index Text -> Text -> Text Source #

unsafeTake :: Index Text -> Text -> Text Source #

drop :: Index Text -> Text -> Text Source #

unsafeDrop :: Index Text -> Text -> Text Source #

dropEnd :: Index Text -> Text -> Text Source #

partition :: (Element Text -> Bool) -> Text -> (Text, Text) Source #

uncons :: Text -> Maybe (Element Text, Text) Source #

unsnoc :: Text -> Maybe (Text, Element Text) Source #

filter :: (Element Text -> Bool) -> Text -> Text Source #

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

replicate :: Index Text -> Element Text -> Text Source #

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

groupBy :: (Element Text -> Element Text -> Bool) -> Text -> [Text] Source #

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

subsequences :: Text -> [Text] Source #

permutations :: Text -> [Text] Source #

tailEx :: Text -> Text Source #

tailMay :: Text -> Maybe Text Source #

initEx :: Text -> Text Source #

initMay :: Text -> Maybe Text Source #

unsafeTail :: Text -> Text Source #

unsafeInit :: Text -> Text Source #

index :: Text -> Index Text -> Maybe (Element Text) Source #

indexEx :: Text -> Index Text -> Element Text Source #

unsafeIndex :: Text -> Index Text -> Element Text Source #

splitWhen :: (Element Text -> Bool) -> Text -> [Text] Source #

IsSequence [a] Source # 
Instance details

Defined in Data.Sequences

Methods

fromList :: [Element [a]] -> [a] Source #

lengthIndex :: [a] -> Index [a] Source #

break :: (Element [a] -> Bool) -> [a] -> ([a], [a]) Source #

span :: (Element [a] -> Bool) -> [a] -> ([a], [a]) Source #

dropWhile :: (Element [a] -> Bool) -> [a] -> [a] Source #

takeWhile :: (Element [a] -> Bool) -> [a] -> [a] Source #

splitAt :: Index [a] -> [a] -> ([a], [a]) Source #

unsafeSplitAt :: Index [a] -> [a] -> ([a], [a]) Source #

take :: Index [a] -> [a] -> [a] Source #

unsafeTake :: Index [a] -> [a] -> [a] Source #

drop :: Index [a] -> [a] -> [a] Source #

unsafeDrop :: Index [a] -> [a] -> [a] Source #

dropEnd :: Index [a] -> [a] -> [a] Source #

partition :: (Element [a] -> Bool) -> [a] -> ([a], [a]) Source #

uncons :: [a] -> Maybe (Element [a], [a]) Source #

unsnoc :: [a] -> Maybe ([a], Element [a]) Source #

filter :: (Element [a] -> Bool) -> [a] -> [a] Source #

filterM :: Monad m => (Element [a] -> m Bool) -> [a] -> m [a] Source #

replicate :: Index [a] -> Element [a] -> [a] Source #

replicateM :: Monad m => Index [a] -> m (Element [a]) -> m [a] Source #

groupBy :: (Element [a] -> Element [a] -> Bool) -> [a] -> [[a]] Source #

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

subsequences :: [a] -> [[a]] Source #

permutations :: [a] -> [[a]] Source #

tailEx :: [a] -> [a] Source #

tailMay :: [a] -> Maybe [a] Source #

initEx :: [a] -> [a] Source #

initMay :: [a] -> Maybe [a] Source #

unsafeTail :: [a] -> [a] Source #

unsafeInit :: [a] -> [a] Source #

index :: [a] -> Index [a] -> Maybe (Element [a]) Source #

indexEx :: [a] -> Index [a] -> Element [a] Source #

unsafeIndex :: [a] -> Index [a] -> Element [a] Source #

splitWhen :: (Element [a] -> Bool) -> [a] -> [[a]] Source #

IsSequence (Seq a) Source # 
Instance details

Defined in Data.Sequences

Methods

fromList :: [Element (Seq a)] -> Seq a Source #

lengthIndex :: Seq a -> Index (Seq a) Source #

break :: (Element (Seq a) -> Bool) -> Seq a -> (Seq a, Seq a) Source #

span :: (Element (Seq a) -> Bool) -> Seq a -> (Seq a, Seq a) Source #

dropWhile :: (Element (Seq a) -> Bool) -> Seq a -> Seq a Source #

takeWhile :: (Element (Seq a) -> Bool) -> Seq a -> Seq a Source #

splitAt :: Index (Seq a) -> Seq a -> (Seq a, Seq a) Source #

unsafeSplitAt :: Index (Seq a) -> Seq a -> (Seq a, Seq a) Source #

take :: Index (Seq a) -> Seq a -> Seq a Source #

unsafeTake :: Index (Seq a) -> Seq a -> Seq a Source #

drop :: Index (Seq a) -> Seq a -> Seq a Source #

unsafeDrop :: Index (Seq a) -> Seq a -> Seq a Source #

dropEnd :: Index (Seq a) -> Seq a -> Seq a Source #

partition :: (Element (Seq a) -> Bool) -> Seq a -> (Seq a, Seq a) Source #

uncons :: Seq a -> Maybe (Element (Seq a), Seq a) Source #

unsnoc :: Seq a -> Maybe (Seq a, Element (Seq a)) Source #

filter :: (Element (Seq a) -> Bool) -> Seq a -> Seq a Source #

filterM :: Monad m => (Element (Seq a) -> m Bool) -> Seq a -> m (Seq a) Source #

replicate :: Index (Seq a) -> Element (Seq a) -> Seq a Source #

replicateM :: Monad m => Index (Seq a) -> m (Element (Seq a)) -> m (Seq a) Source #

groupBy :: (Element (Seq a) -> Element (Seq a) -> Bool) -> Seq a -> [Seq a] Source #

groupAllOn :: Eq b => (Element (Seq a) -> b) -> Seq a -> [Seq a] Source #

subsequences :: Seq a -> [Seq a] Source #

permutations :: Seq a -> [Seq a] Source #

tailEx :: Seq a -> Seq a Source #

tailMay :: Seq a -> Maybe (Seq a) Source #

initEx :: Seq a -> Seq a Source #

initMay :: Seq a -> Maybe (Seq a) Source #

unsafeTail :: Seq a -> Seq a Source #

unsafeInit :: Seq a -> Seq a Source #

index :: Seq a -> Index (Seq a) -> Maybe (Element (Seq a)) Source #

indexEx :: Seq a -> Index (Seq a) -> Element (Seq a) Source #

unsafeIndex :: Seq a -> Index (Seq a) -> Element (Seq a) Source #

splitWhen :: (Element (Seq a) -> Bool) -> Seq a -> [Seq a] Source #

Unbox a => IsSequence (Vector a) Source # 
Instance details

Defined in Data.Sequences

Methods

fromList :: [Element (Vector a)] -> Vector a Source #

lengthIndex :: Vector a -> Index (Vector a) Source #

break :: (Element (Vector a) -> Bool) -> Vector a -> (Vector a, Vector a) Source #

span :: (Element (Vector a) -> Bool) -> Vector a -> (Vector a, Vector a) Source #

dropWhile :: (Element (Vector a) -> Bool) -> Vector a -> Vector a Source #

takeWhile :: (Element (Vector a) -> Bool) -> Vector a -> Vector a Source #

splitAt :: Index (Vector a) -> Vector a -> (Vector a, Vector a) Source #

unsafeSplitAt :: Index (Vector a) -> Vector a -> (Vector a, Vector a) Source #

take :: Index (Vector a) -> Vector a -> Vector a Source #

unsafeTake :: Index (Vector a) -> Vector a -> Vector a Source #

drop :: Index (Vector a) -> Vector a -> Vector a Source #

unsafeDrop :: Index (Vector a) -> Vector a -> Vector a Source #

dropEnd :: Index (Vector a) -> Vector a -> Vector a Source #

partition :: (Element (Vector a) -> Bool) -> Vector a -> (Vector a, Vector a) Source #

uncons :: Vector a -> Maybe (Element (Vector a), Vector a) Source #

unsnoc :: Vector a -> Maybe (Vector a, Element (Vector a)) Source #

filter :: (Element (Vector a) -> Bool) -> Vector a -> Vector a Source #

filterM :: Monad m => (Element (Vector a) -> m Bool) -> Vector a -> m (Vector a) Source #

replicate :: Index (Vector a) -> Element (Vector a) -> Vector a Source #

replicateM :: Monad m => Index (Vector a) -> m (Element (Vector a)) -> m (Vector a) Source #

groupBy :: (Element (Vector a) -> Element (Vector a) -> Bool) -> Vector a -> [Vector a] Source #

groupAllOn :: Eq b => (Element (Vector a) -> b) -> Vector a -> [Vector a] Source #

subsequences :: Vector a -> [Vector a] Source #

permutations :: Vector a -> [Vector a] Source #

tailEx :: Vector a -> Vector a Source #

tailMay :: Vector a -> Maybe (Vector a) Source #

initEx :: Vector a -> Vector a Source #

initMay :: Vector a -> Maybe (Vector a) Source #

unsafeTail :: Vector a -> Vector a Source #

unsafeInit :: Vector a -> Vector a Source #

index :: Vector a -> Index (Vector a) -> Maybe (Element (Vector a)) Source #

indexEx :: Vector a -> Index (Vector a) -> Element (Vector a) Source #

unsafeIndex :: Vector a -> Index (Vector a) -> Element (Vector a) Source #

splitWhen :: (Element (Vector a) -> Bool) -> Vector a -> [Vector a] Source #

Storable a => IsSequence (Vector a) Source # 
Instance details

Defined in Data.Sequences

Methods

fromList :: [Element (Vector a)] -> Vector a Source #

lengthIndex :: Vector a -> Index (Vector a) Source #

break :: (Element (Vector a) -> Bool) -> Vector a -> (Vector a, Vector a) Source #

span :: (Element (Vector a) -> Bool) -> Vector a -> (Vector a, Vector a) Source #

dropWhile :: (Element (Vector a) -> Bool) -> Vector a -> Vector a Source #

takeWhile :: (Element (Vector a) -> Bool) -> Vector a -> Vector a Source #

splitAt :: Index (Vector a) -> Vector a -> (Vector a, Vector a) Source #

unsafeSplitAt :: Index (Vector a) -> Vector a -> (Vector a, Vector a) Source #

take :: Index (Vector a) -> Vector a -> Vector a Source #

unsafeTake :: Index (Vector a) -> Vector a -> Vector a Source #

drop :: Index (Vector a) -> Vector a -> Vector a Source #

unsafeDrop :: Index (Vector a) -> Vector a -> Vector a Source #

dropEnd :: Index (Vector a) -> Vector a -> Vector a Source #

partition :: (Element (Vector a) -> Bool) -> Vector a -> (Vector a, Vector a) Source #

uncons :: Vector a -> Maybe (Element (Vector a), Vector a) Source #

unsnoc :: Vector a -> Maybe (Vector a, Element (Vector a)) Source #

filter :: (Element (Vector a) -> Bool) -> Vector a -> Vector a Source #

filterM :: Monad m => (Element (Vector a) -> m Bool) -> Vector a -> m (Vector a) Source #

replicate :: Index (Vector a) -> Element (Vector a) -> Vector a Source #

replicateM :: Monad m => Index (Vector a) -> m (Element (Vector a)) -> m (Vector a) Source #

groupBy :: (Element (Vector a) -> Element (Vector a) -> Bool) -> Vector a -> [Vector a] Source #

groupAllOn :: Eq b => (Element (Vector a) -> b) -> Vector a -> [Vector a] Source #

subsequences :: Vector a -> [Vector a] Source #

permutations :: Vector a -> [Vector a] Source #

tailEx :: Vector a -> Vector a Source #

tailMay :: Vector a -> Maybe (Vector a) Source #

initEx :: Vector a -> Vector a Source #

initMay :: Vector a -> Maybe (Vector a) Source #

unsafeTail :: Vector a -> Vector a Source #

unsafeInit :: Vector a -> Vector a Source #

index :: Vector a -> Index (Vector a) -> Maybe (Element (Vector a)) Source #

indexEx :: Vector a -> Index (Vector a) -> Element (Vector a) Source #

unsafeIndex :: Vector a -> Index (Vector a) -> Element (Vector a) Source #

splitWhen :: (Element (Vector a) -> Bool) -> Vector a -> [Vector a] Source #

IsSequence (Vector a) Source # 
Instance details

Defined in Data.Sequences

Methods

fromList :: [Element (Vector a)] -> Vector a Source #

lengthIndex :: Vector a -> Index (Vector a) Source #

break :: (Element (Vector a) -> Bool) -> Vector a -> (Vector a, Vector a) Source #

span :: (Element (Vector a) -> Bool) -> Vector a -> (Vector a, Vector a) Source #

dropWhile :: (Element (Vector a) -> Bool) -> Vector a -> Vector a Source #

takeWhile :: (Element (Vector a) -> Bool) -> Vector a -> Vector a Source #

splitAt :: Index (Vector a) -> Vector a -> (Vector a, Vector a) Source #

unsafeSplitAt :: Index (Vector a) -> Vector a -> (Vector a, Vector a) Source #

take :: Index (Vector a) -> Vector a -> Vector a Source #

unsafeTake :: Index (Vector a) -> Vector a -> Vector a Source #

drop :: Index (Vector a) -> Vector a -> Vector a Source #

unsafeDrop :: Index (Vector a) -> Vector a -> Vector a Source #

dropEnd :: Index (Vector a) -> Vector a -> Vector a Source #

partition :: (Element (Vector a) -> Bool) -> Vector a -> (Vector a, Vector a) Source #

uncons :: Vector a -> Maybe (Element (Vector a), Vector a) Source #

unsnoc :: Vector a -> Maybe (Vector a, Element (Vector a)) Source #

filter :: (Element (Vector a) -> Bool) -> Vector a -> Vector a Source #

filterM :: Monad m => (Element (Vector a) -> m Bool) -> Vector a -> m (Vector a) Source #

replicate :: Index (Vector a) -> Element (Vector a) -> Vector a Source #

replicateM :: Monad m => Index (Vector a) -> m (Element (Vector a)) -> m (Vector a) Source #

groupBy :: (Element (Vector a) -> Element (Vector a) -> Bool) -> Vector a -> [Vector a] Source #

groupAllOn :: Eq b => (Element (Vector a) -> b) -> Vector a -> [Vector a] Source #

subsequences :: Vector a -> [Vector a] Source #

permutations :: Vector a -> [Vector a] Source #

tailEx :: Vector a -> Vector a Source #

tailMay :: Vector a -> Maybe (Vector a) Source #

initEx :: Vector a -> Vector a Source #

initMay :: Vector a -> Maybe (Vector a) Source #

unsafeTail :: Vector a -> Vector a Source #

unsafeInit :: Vector a -> Vector a Source #

index :: Vector a -> Index (Vector a) -> Maybe (Element (Vector a)) Source #

indexEx :: Vector a -> Index (Vector a) -> Element (Vector a) Source #

unsafeIndex :: Vector a -> Index (Vector a) -> Element (Vector a) Source #

splitWhen :: (Element (Vector a) -> Bool) -> Vector a -> [Vector a] Source #

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.

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

splitElem :: (IsSequence seq, Eq (Element seq)) => 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 :: (IsSequence seq, Eq (Element seq)) => seq -> seq -> [seq] Source #

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

ointercalate 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

replaceSeq :: (IsSequence seq, Eq (Element seq)) => seq -> seq -> seq -> seq Source #

replaceSeq old new replaces all old subsequences with new.

replaceSeq old new === ointercalate new . splitSeq old

Since: 1.0.1

stripPrefix :: (IsSequence seq, Eq (Element seq)) => 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 "bar"
> stripPrefix "abc" "foobar"
Nothing

stripSuffix :: (IsSequence seq, Eq (Element seq)) => 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

dropPrefix :: (IsSequence seq, Eq (Element seq)) => seq -> seq -> seq Source #

dropPrefix drops the given prefix from a sequence. It returns the original sequence if the sequence doesn't start with the given prefix.

> dropPrefix "foo" "foobar"
"bar"
> dropPrefix "abc" "foobar"
"foobar"

Since: 1.0.7.0

dropSuffix :: (IsSequence seq, Eq (Element seq)) => seq -> seq -> seq Source #

dropSuffix drops the given suffix from a sequence. It returns the original sequence if the sequence doesn't end with the given suffix.

> dropSuffix "bar" "foobar"
"foo"
> dropSuffix "abc" "foobar"
"foobar"

Since: 1.0.7.0

ensurePrefix :: (Eq (Element seq), IsSequence seq) => seq -> seq -> seq Source #

ensurePrefix will add a prefix to a sequence if it doesn't exist, and otherwise have no effect.

> ensurePrefix "foo" "foobar"
"foobar"
> ensurePrefix "abc" "foobar"
"abcfoobar"

Since: 1.0.3

ensureSuffix :: (Eq (Element seq), IsSequence seq) => seq -> seq -> seq Source #

Append a suffix to a sequence, unless it already has that suffix.

> ensureSuffix "bar" "foobar"
"foobar"
> ensureSuffix "abc" "foobar"
"foobarabc"

Since: 1.0.3

isPrefixOf :: (IsSequence seq, Eq (Element seq)) => seq -> seq -> Bool Source #

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

isSuffixOf :: (IsSequence seq, Eq (Element seq)) => seq -> seq -> Bool Source #

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

isInfixOf :: (IsSequence seq, Eq (Element seq)) => 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 :: (IsSequence seq, Eq (Element seq)) => seq -> [seq] Source #

Equivalent to groupBy (==)

groupAll :: (IsSequence seq, Eq (Element seq)) => seq -> [seq] Source #

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

Equivalent to groupAllOn id

delete :: (IsSequence seq, Eq (Element seq)) => Element seq -> seq -> seq Source #

Since: 0.10.2

deleteBy :: (IsSequence seq, Eq (Element seq)) => (Element seq -> Element seq -> Bool) -> Element seq -> seq -> seq Source #

Since: 0.10.2

sort :: (SemiSequence seq, Ord (Element seq)) => 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 :: (Element seq ~ t, MonoFoldable seq) => seq -> 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 :: (Element seq ~ t, MonoFoldable seq) => seq -> 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
Textual Text Source # 
Instance details

Defined in Data.Sequences

Textual Text Source # 
Instance details

Defined in Data.Sequences

c ~ Char => Textual [c] Source # 
Instance details

Defined in Data.Sequences

Methods

words :: [c] -> [[c]] Source #

unwords :: (Element seq ~ [c], MonoFoldable seq) => seq -> [c] Source #

lines :: [c] -> [[c]] Source #

unlines :: (Element seq ~ [c], MonoFoldable seq) => seq -> [c] Source #

toLower :: [c] -> [c] Source #

toUpper :: [c] -> [c] Source #

toCaseFold :: [c] -> [c] Source #

breakWord :: [c] -> ([c], [c]) Source #

breakLine :: [c] -> ([c], [c]) Source #

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

class (IsSequence lazy, IsSequence strict) => LazySequence lazy strict | lazy -> strict, strict -> lazy where Source #

Lazy sequences containing strict chunks of data.

Since: 1.0.0

Methods

toChunks :: lazy -> [strict] Source #

fromChunks :: [strict] -> lazy Source #

toStrict :: lazy -> strict Source #

fromStrict :: strict -> lazy Source #

pack :: IsSequence seq => [Element seq] -> seq Source #

Synonym for fromList

Since: 1.0.0

unpack :: MonoFoldable mono => mono -> [Element mono] Source #

Synonym for otoList

Since: 1.0.0

repack :: (MonoFoldable a, IsSequence b, Element a ~ Element b) => a -> b Source #

Repack from one type to another, dropping to a list in the middle.

repack = pack . unpack.

Since: 1.0.0

class (Textual textual, IsSequence binary) => Utf8 textual binary | textual -> binary, binary -> textual where Source #

Textual data which can be encoded to and decoded from UTF8.

Since: 1.0.0

Methods

encodeUtf8 :: textual -> binary Source #

Encode from textual to binary using UTF-8 encoding

Since: 1.0.0

decodeUtf8 :: binary -> textual Source #

Note that this function is required to be pure. In the case of a decoding error, Unicode replacement characters must be used.

Since: 1.0.0

Instances
Utf8 Text ByteString Source # 
Instance details

Defined in Data.Sequences

Utf8 Text ByteString Source # 
Instance details

Defined in Data.Sequences

(c ~ Char, w ~ Word8) => Utf8 [c] [w] Source # 
Instance details

Defined in Data.Sequences

Methods

encodeUtf8 :: [c] -> [w] Source #

decodeUtf8 :: [w] -> [c] Source #