mcsp-algorithms-0.1.0: Algorithms for Minimum Common String Partition (MCSP) in Haskell.
Safe HaskellSafe-Inferred
LanguageGHC2021

MCSP.Data.String

Description

Generic strings using backed by a contiguous array of unboxed characters.

Synopsis

Unboxed string

data String a Source #

An unboxed string of characters a.

Implemented as a contiguous vector of unboxed characters.

Constructors

Unbox a => String !(Vector a)

Construct a string from a unboxed vector.

Note that Unbox is only required for constructing the string. All other operations should be possible without that constraint.

Bundled Patterns

pattern Unboxed :: () => Unbox a => String a

Proves Unbox from an already constructed string.

This pattern is useful for matching in operations where Unbox a is required.

>>> import GHC.Base (asTypeOf)
>>> emptyLike s = asTypeOf empty s
>>> :t emptyLike
emptyLike :: Unbox a => String a -> String a
>>> emptyLike' s@Unboxed = asTypeOf empty s
>>> :t emptyLike'
emptyLike' :: String a -> String a
pattern Null :: () => Unbox a => String a

O(1) Matches the empty string.

>>> [s | s@Null <- ["", "a", "ab", "", "abc"]]
[,]
pattern NonNull :: () => Unbox a => String a -> String a

O(1) Matches any non-empty string.

>>> [s | NonNull s <- ["", "a", "ab", "", "abc"]]
[a,ab,abc]
pattern Head :: () => Unbox a => a -> String a

O(1) Matches the first character in a string.

>>> [c | Head c <- ["", "a", "ab", "", "abc"]]
"aaa"
pattern Last :: () => Unbox a => a -> String a

O(1) Matches the last character in a string.

>>> [c | Last c <- ["", "a", "ab", "", "abc"]]
"abc"
pattern Singleton :: () => Unbox a => a -> String a

O(1) Matches a string composed of a single character.

>>> [c | Singleton c <- ["", "a", "ab", "", "abc"]]
"a"
pattern (:<) :: () => Unbox a => a -> String a -> String a

O(1) Matches head and tail of a string, if present.

>>> [(h,t) | h :< t <- ["", "a", "ab", "", "abc"]]
[('a',),('a',b),('a',bc)]
pattern (:>) :: () => Unbox a => String a -> a -> String a

O(1) Matches init and last of a string, if present.

>>> [(i,l) | i :> l <- ["", "a", "ab", "", "abc"]]
[(,'a'),(a,'b'),(ab,'c')]
pattern (:<:) :: () => Unbox a => String a -> String a -> String a

O(1) Stringified :<, matching head and tail.

>>> [(h,t) | h :<: t <- ["", "a", "ab", "", "abc"]]
[(a,),(a,b),(a,bc)]
pattern (:>:) :: () => Unbox a => String a -> String a -> String a

O(1) Stringified :>, matching init and last.

>>> [(i,l) | i :>: l <- ["", "a", "ab", "", "abc"]]
[(,a),(a,b),(ab,c)]

Instances

Instances details
Foldable String Source # 
Instance details

Defined in MCSP.Data.String

Methods

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

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

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

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

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

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

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

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

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

toList :: String a -> [a] #

null :: String a -> Bool #

length :: String a -> Int #

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

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

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

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

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

NFData1 String Source # 
Instance details

Defined in MCSP.Data.String

Methods

liftRnf :: (a -> ()) -> String a -> () #

Unbox a => Vector String a Source # 
Instance details

Defined in MCSP.Data.String

Methods

basicUnsafeFreeze :: Mutable String s a -> ST s (String a)

basicUnsafeThaw :: String a -> ST s (Mutable String s a)

basicLength :: String a -> Int

basicUnsafeSlice :: Int -> Int -> String a -> String a

basicUnsafeIndexM :: String a -> Int -> Box a

basicUnsafeCopy :: Mutable String s a -> String a -> ST s ()

elemseq :: String a -> a -> b -> b

a ~ Char => IsString (String a) Source #

String Char can be written using String syntax ("abcd").

Instance details

Defined in MCSP.Data.String

Methods

fromString :: String0 -> String a #

Unbox a => Monoid (String a) Source #

Monoid based on concatenation (mempty == "").

Instance details

Defined in MCSP.Data.String

Methods

mempty :: String a #

mappend :: String a -> String a -> String a #

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

Semigroup (String a) Source #

Semigroup based on concatenation ("a" <> "b" == "ab").

Instance details

Defined in MCSP.Data.String

Methods

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

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

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

Unbox a => IsList (String a) Source # 
Instance details

Defined in MCSP.Data.String

Associated Types

type Item (String a) #

Methods

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

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

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

(Unbox a, ReadString a) => Read (String a) Source # 
Instance details

Defined in MCSP.Data.String

ShowString a => Show (String a) Source # 
Instance details

Defined in MCSP.Data.String

Methods

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

show :: String a -> String0 #

showList :: [String a] -> ShowS #

NFData (String a) Source # 
Instance details

Defined in MCSP.Data.String

Methods

rnf :: String a -> () #

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

Defined in MCSP.Data.String

Methods

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

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

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

Defined in MCSP.Data.String

Methods

compare :: String a -> String a -> Ordering #

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

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

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

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

max :: String a -> String a -> String a #

min :: String a -> String a -> String a #

type Mutable String Source # 
Instance details

Defined in MCSP.Data.String

type Mutable String
type Item (String a) Source # 
Instance details

Defined in MCSP.Data.String

type Item (String a) = a

class (Vector Vector a, MVector MVector a) => Unbox a #

Instances

Instances details
Unbox All 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Any 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Word64 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox () 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Char 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Double 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Float 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Int 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox Word 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Complex a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Down a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (First a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Last a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Max a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Min a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (WrappedMonoid a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Dual a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Product a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Sum a) 
Instance details

Defined in Data.Vector.Unboxed.Base

(Unbox a, Unbox b) => Unbox (Arg a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

(Unbox a, Unbox b) => Unbox (a, b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => Unbox (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox (f a) => Unbox (Alt f a) 
Instance details

Defined in Data.Vector.Unboxed.Base

(Unbox a, Unbox b, Unbox c) => Unbox (a, b, c) 
Instance details

Defined in Data.Vector.Unboxed.Base

(Unbox a, Unbox b, Unbox c, Unbox d) => Unbox (a, b, c, d) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox (f (g a)) => Unbox (Compose f g a) 
Instance details

Defined in Data.Vector.Unboxed.Base

(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => Unbox (a, b, c, d, e) 
Instance details

Defined in Data.Vector.Unboxed.Base

(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => Unbox (a, b, c, d, e, f) 
Instance details

Defined in Data.Vector.Unboxed.Base

Text IO

Accessors

Length information

length :: String a -> Int Source #

O(1) Yield the length of the string.

null :: String a -> Bool Source #

O(1) Test whether a string is empty.

Indexing

(!) :: String a -> Int -> a Source #

O(1) Indexing.

>>> "abc" ! 1
'b'

(!?) :: String a -> Int -> Maybe a Source #

O(1) Safe indexing.

>>> "abc" !? 1
Just 'b'
>>> "abc" !? 3
Nothing

head :: String a -> a Source #

O(1) First character.

>>> head "hello"
'h'

last :: String a -> a Source #

O(1) Last character.

>>> last "hello"
'o'

unsafeIndex :: String a -> Int -> a Source #

O(1) Unsafe indexing without bounds checking.

single :: String a -> Maybe a Source #

O(1) The character of a singleton string.

>>> single ""
Nothing
>>> single "x"
Just 'x'
>>> single "xy"
Nothing

indexM :: (Alternative m, Monad m) => String a -> Int -> m a Source #

O(1) Indexing in a monad.

See Data.Vactor.Unbox.

>>> indexM @Maybe "xyz" 5
Nothing

headM :: (Alternative m, Monad m) => String a -> m a Source #

O(1) First character of a string in a monad.

See Data.Vactor.Unbox.

>>> headM @Maybe ""
Nothing

lastM :: (Alternative m, Monad m) => String a -> m a Source #

O(1) Last character of a string in a monad.

See Data.Vactor.Unbox.

>>> lastM @Maybe ""
Nothing

Substrings (slicing)

slice :: Int -> Int -> String a -> String a Source #

O(1) Yield the slice `s[i:i+n]` of the string without copying it.

The string must contain at least `i+n` characters.

>>> slice 2 3 "genome"
nom

init :: String a -> String a Source #

O(1) Yield all but the last character without copying.

The string may not be empty.

>>> init "genome"
genom

tail :: String a -> String a Source #

O(1) Yield all but the first character without copying.

The string may not be empty.

>>> tail "genome"
enome

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

O(1) Yield at the first n characters without copying.

The string may contain less than n characters, in which case it is returned unchanged.

>>> take 2 "hello"
he
>>> take 10 "hello"
hello

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

O(1) Yield all but the first n characters without copying.

The string may contain less than n characters, in which case an empty string is returned.

>>> drop 2 "hello"
llo
>>> drop 10 "hello"

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

O(1) Yield the first n characters paired with the remainder, without copying.

Note that `splitAt n s` is equivalent to `(take n s, drop n s)`, but slightly more efficient.

>>> splitAt 6 "babushka"
(babush,ka)

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

O(1) Yield the head and tail of the string, or Nothing if it is empty.

>>> uncons "acgt"
Just ('a',cgt)

unsnoc :: String a -> Maybe (String a, a) Source #

O(1) Yield the init and last of the string, or Nothing if it is empty.

>>> unsnoc "acgt"
Just (acg,'t')

unsafeSlice :: Int -> Int -> String a -> String a Source #

O(1) Yield a slice of the string without copying.

The string must contain at least `i+n` characters, but this is not checked.

Construction

Initialisation

empty :: Unbox a => String a Source #

O(1) The empty string.

>>> empty == ""
True

singleton :: Unbox a => a -> String a Source #

O(1) A string with exactly one character.

>>> singleton 's'
s

replicate :: Unbox a => Int -> a -> String a Source #

O(n) A string of the given length with the same character in each position.

>>> replicate 10 'a'
aaaaaaaaaa

generate :: Unbox a => Int -> (Int -> a) -> String a Source #

O(n) Construct a string of the given length by applying the function to each index.

>>> import Prelude (head, show)
>>> generate 5 (\i -> Prelude.head (show i))
01234

Monadic initialisation

replicateM :: (Unbox a, Monad m) => Int -> m a -> m (String a) Source #

O(n) Execute the monadic action the given number of times and store the results in a string.

>>> replicateM 4 (Just 'v')
Just vvvv

generateM :: (Unbox a, Monad m) => Int -> (Int -> m a) -> m (String a) Source #

O(n) Construct a string of the given length by applying the monadic action to each index.

>>> generateM 5 (\i -> Just i)
Just 0 1 2 3 4

create :: Unbox a => (forall s. ST s (MVector s a)) -> String a Source #

O(f(n)) Execute the monadic action and freeze the resulting string.

>>> import Control.Applicative (pure)
>>> import Data.Vector.Unboxed.Mutable (new, write)
>>> create (do v <- new 2; write v 0 'a'; write v 1 'b'; pure v)
ab

Unfolding

unfoldr :: Unbox a => (b -> Maybe (a, b)) -> b -> String a Source #

O(n) Construct a string by repeatedly applying the generator function to a seed.

The generator function yields -- Just the next character and the new seed or Nothing if there are no more characters.

>>> unfoldr @Int (\n -> if n == 0 then Nothing else Just (n, n-1)) 10
10 9 8 7 6 5 4 3 2 1

unfoldrExactN :: Unbox a => Int -> (b -> (a, b)) -> b -> String a Source #

O(n) Construct a vector with exactly n characters by repeatedly applying the generator function to a seed.

The generator function yields the next character and the new seed.

>>> unfoldrExactN @Int 3 (\n -> (n, n-1)) 10
10 9 8

unfoldrM :: (Unbox a, Monad m) => (b -> m (Maybe (a, b))) -> b -> m (String a) Source #

O(n) Construct a string by repeatedly applying the generator function to a seed.

The generator function yields -- Just the next character and the new seed or Nothing if there are no more characters.

>>> unfoldr @Int (\n -> if n == 0 then Nothing else Just (n, n-1)) 10
10 9 8 7 6 5 4 3 2 1

unfoldrExactNM :: (Unbox a, Monad m) => Int -> (b -> m (a, b)) -> b -> m (String a) Source #

O(n) Construct a string with exactly n characters by repeatedly applying the generator function to a seed.

The generator function yields the next character and the new seed.

>>> unfoldrExactN @Int 3 (\n -> (n, n-1)) 10
10 9 8

Enumeration

enumFromN :: (Unbox a, Num a) => a -> Int -> String a Source #

O(n) Yield a string of the given length, containing the characters x, x+1 etc.

This operation is usually more efficient than enumFromTo.

>>> enumFromN @Int 5 3
5 6 7

enumFromStepN :: (Unbox a, Num a) => a -> a -> Int -> String a Source #

O(n) Yield a string of the given length, containing the characters x, x+y, x+y+y etc.

This operations is usually more efficient than enumFromThenTo.

>>> enumFromStepN @Int 1 2 5
1 3 5 7 9

Concatenation

cons :: a -> String a -> String a Source #

O(n) Prepend a character.

>>> cons 'e' "xtrem"
extrem

snoc :: String a -> a -> String a Source #

O(n) Append a character.

>>> snoc "xtrem" 'a'
xtrema

(++) :: String a -> String a -> String a Source #

O(m+n) Concatenate two strings.

>>> "abc" ++ "xyz"
abcxyz

concat :: Unbox a => [String a] -> String a Source #

O(n) Concatenate all strings in the list.

This is the simplest variant, but requires `Unbox a`.

>>> concat ["abc", "123", "def"]
abc123def
>>> concat @Char []

concatNE :: NonEmpty (String a) -> String a Source #

O(n) Concatenate all strings in the non-empty list.

>>> concatNE ("abc" :| ["123", "def"])
abc123def

Restricting memory usage

force :: String a -> String a Source #

O(n) Yield the argument, but force it not to retain any extra memory, possibly by copying it.

See Data.Vector.Unbox.

Modifying vectors

Bulk updates

(//) :: String a -> [(Int, a)] -> String a Source #

O(m+n) For each pair `(i,a)` from the list of index/value pairs, replace the character at position i by a.

>>> "test" // [(2,'x'),(0,'y'),(2,'z')]
yezt

update :: String a -> [Int] -> String a -> String a Source #

O(m+min(n1,n2)) For each index i from the index list and the corresponding value a from another string, replace the character of the initial string at position i by a.

>>> update "test" [2,0,2] "xyz"
yezt

Accumulations

accum :: (a -> b -> a) -> String a -> [(Int, b)] -> String a Source #

O(m+n) For each pair (i,b) from the list, replace the character at position i by f a b.

>>> import GHC.Num ((+))
>>> accum @Int (+) [1000,2000,3000] [(2,4),(1,6),(0,3),(1,10)]
1003 2016 3004

accumulate :: (a -> b -> a) -> String a -> [Int] -> String b -> String a Source #

O(m+min(n1,n2)) For each index i from the index list and the corresponding value b from the string, replace the character of the initial string at position i by f a b.

>>> import GHC.Num ((+))
>>> accumulate @Int (+) [5,9,2] [2,1,0,1] [4,6,3,7]
8 22 6

Permutations

reverse :: String a -> String a Source #

O(n) Reverse a string.

>>> reverse "abc123"
321cba

backpermute :: String a -> [Int] -> String a Source #

O(n) Yield the string obtained by replacing each element i of the index list by `xs!i`.

This is equivalent to `map (xs!)` is, but is often much more efficient.

>>> backpermute "abcd" [0,3,2,3,1,0]
adcdba

Safe destructive updates

modify :: (forall s. MVector s a -> ST s ()) -> String a -> String a Source #

O(f(n)) Apply a destructive operation to a string.

The operation will be performed in place if it is safe to do so and will modify a copy of the vector otherwise.

>>> import Data.Vector.Unboxed.Mutable (write)
>>> modify (\v -> write v 3 'X') (replicate 10 'a')
aaaXaaaaaa

Elementwise operations

Indexing

indexed :: String a -> String (Int, a) Source #

O(n) Pair each character in a string with its index.

>>> indexed "greedy"
(0,'g') (1,'r') (2,'e') (3,'e') (4,'d') (5,'y')

Mapping

map :: Unbox b => (a -> b) -> String a -> String b Source #

O(n) Map a function over a string.

>>> import Data.Char (ord)
>>> map ord "genome"
103 101 110 111 109 101

map_ :: (a -> a) -> String a -> String a Source #

O(n) Map an endofunction over a string.

>>> import Data.Char (toUpper)
>>> map_ toUpper "genome"
GENOME

imap :: Unbox b => (Int -> a -> b) -> String a -> String b Source #

O(n) Apply a function to every character of a string and its index.

>>> import Data.Char (ord)
>>> import GHC.Num ((+))
>>> imap (\i c -> i + ord c) "genome"
103 102 112 114 113 106

imap_ :: (Int -> a -> a) -> String a -> String a Source #

O(n) Apply an endofunction to every character of a string and its index.

>>> import Data.Char (chr, ord)
>>> import GHC.Num ((+))
>>> imap_ (\i c -> chr (i + ord c)) "genome"
gfprqj

concatMap :: Unbox b => (a -> [b]) -> String a -> String b Source #

O(?) Map a function over a string and concatenate the results.

>>> concatMap (\c -> [c, c]) "genome"
ggeennoommee

concatMap_ :: (a -> String a) -> String a -> String a Source #

O(?) Map a function over a string and concatenate the resulting strings.

>>> concatMap_ (\c -> replicate 3 c) "gen"
gggeeennn

mapM :: (Monad m, Unbox b) => (a -> m b) -> String a -> m (String b) Source #

O(n) Apply the monadic action to all characters of the string, yielding a string of results.

mapM_ :: Monad m => (a -> m a) -> String a -> m (String a) Source #

O(n) Apply the monadic action to all characters of the string, yielding a string of results.

forM :: Monad m => String a -> (a -> m b) -> m () Source #

O(n) Apply the monadic action to all characters of a string and ignore the results.

iforM :: Monad m => String a -> (Int -> a -> m b) -> m () Source #

O(n) Apply the monadic action to all characters of a string and their indices and ignore the results.

Zipping

zipWith :: Unbox c => (a -> b -> c) -> String a -> String b -> String c Source #

O(min(m,n)) Zip two strings with the given function.

zipWith3 :: Unbox d => (a -> b -> c -> d) -> String a -> String b -> String c -> String d Source #

O(min(m,n,k)) Zip three strings with the given function.

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

O(min(m,n)) Zip two strings.

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

O(min(m,n)) Zip three strings.

zipWithM :: (Monad m, Unbox c) => (a -> b -> m c) -> String a -> String b -> m (String c) Source #

O(min(m,n)) Zip the two strings with the monadic action and yield a vector of results.

zipWithM_ :: Monad m => (a -> b -> m c) -> String a -> String b -> m () Source #

O(min(m,n)) Zip the two strings with the monadic action and ignore the results.

unzip :: (Unbox a, Unbox b) => String (a, b) -> (String a, String b) Source #

O(n) Unzip a string of pairs.

unzip3 :: (Unbox a, Unbox b) => String (a, b) -> (String a, String b) Source #

O(n) Unzip a string of triples.

Working with predicates

Filtering

filter :: (a -> Bool) -> String a -> String a Source #

O(n) Drop all characters that do not satisfy the predicate.

>>> import Data.Char (isUpper)
>>> filter isUpper "ABCdefGHI"
ABCGHI

ifilter :: (Int -> a -> Bool) -> String a -> String a Source #

O(n) Drop all characters that do not satisfy the predicate which is applied to the values and their indices.

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

O(n) Drop all characters that do not satisfy the monadic predicate.

uniq :: Eq a => String a -> String a Source #

O(n) Drop repeated adjacent characters.

>>> uniq "aaaabbbcccaabc"
abcabc

mapMaybe :: Unbox b => (a -> Maybe b) -> String a -> String b Source #

O(n) Map the values and collect the Just results.

mapMaybeM :: (Monad m, Unbox b) => (a -> m (Maybe b)) -> String a -> m (String b) Source #

O(n) Apply the monadic function to each element of the string and discard characters returning Nothing.

takeWhile :: (a -> Bool) -> String a -> String a Source #

O(n) Yield the longest prefix of characters satisfying the predicate.

The current implementation is not copy-free, unless the result string is fused away.

dropWhile :: (a -> Bool) -> String a -> String a Source #

O(n) Drop the longest prefix of characters that satisfy the predicate without copying.

Partitioning

partition :: (a -> Bool) -> String a -> (String a, String a) Source #

O(n) Split the string in two parts, the first one containing those characters that satisfy the predicate and the second one those that don't.

The relative order of the characters is preserved at the cost of a sometimes reduced performance compared to unstablePartition.

partitionWith :: (Unbox b, Unbox c) => (a -> Either b c) -> String a -> (String b, String c) Source #

O(n) Split the string into two parts, the first one containing the Left characters and the second containing the Right characters.

The relative order of the characters is preserved.

unstablePartition :: (a -> Bool) -> String a -> (String a, String a) Source #

O(n) Split the string in two parts, the first one containing those characters that satisfy the predicate and the second one those that don't.

The order of the characters is not preserved, but the operation is often faster than partition.

span :: (a -> Bool) -> String a -> (String a, String a) Source #

O(n) Split the string into the longest prefix of characters that satisfy the predicate and the rest without copying.

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

O(n) Split the string into the longest prefix of characters that do not satisfy the predicate and the rest without copying.

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

O(n) Split a string into a list of slices.

The concatenation of this list of slices is equal to the argument string, and each slice contains only equal characters, as determined by the equality predicate function.

>>> import Data.Char (isUpper)
>>> groupBy (\x y -> isUpper x == isUpper y) "Rio Grande"
[R,io ,G,rande]

group :: Eq a => String a -> [String a] Source #

O(n) Split a string into a list of slices.

The concatenation of this list of slices is equal to the argument string, and each slice contains only equal characters.

This is the equivalent of 'groupBy (==)'.

>>> group "Mississippi"
[M,i,ss,i,ss,i,pp,i]

Searching

elem :: Eq a => a -> String a -> Bool Source #

O(n) Check if the string contains a character.

notElem :: Eq a => a -> String a -> Bool Source #

O(n) Check if the string does not contain a character (inverse of elem).

find :: (a -> Bool) -> String a -> Maybe a Source #

O(n) Yield Just the first character matching the predicate or Nothing if no such character exists.

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

O(n) Yield Just the index of the first character matching the predicate or Nothing if no such character exists.

findIndexR :: (a -> Bool) -> String a -> Maybe Int Source #

O(n) Yield Just the index of the last character matching the predicate or Nothing if no such character exists.

findIndices :: (a -> Bool) -> String a -> String Int Source #

O(n) Yield the indices of character satisfying the predicate in ascending order.

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

O(n) Yield Just the index of the first occurrence of the given character or Nothing if the vector does not contain the character.

This is a specialised version of findIndex.

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

O(n) Yield the indices of all occurrences of the given character in ascending order.

This is a specialised version of findIndices.

Utilities

eqBy :: (a -> b -> Bool) -> String a -> String b -> Bool Source #

O(n) Check if two strings are equal using the supplied equality predicate.

>>> import Data.Char (toLower)
>>> eqBy (\x y -> toLower x == toLower y) "ABcd" "abcD"
True

cmpBy :: (a -> b -> Ordering) -> String a -> String b -> Ordering Source #

O(n) Compare two strings using the supplied comparison function for characters.

Comparison works the same as for lists.

convert :: Vector v a => String a -> v a Source #

O(n) Convert to a vector of characters.