| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
System.OsString.Windows.Compat
Synopsis
- data WindowsString
- data WindowsChar
- encodeUtf :: MonadThrow m => String -> m WindowsString
- unsafeEncodeUtf :: HasCallStack => String -> WindowsString
- encodeWith :: TextEncoding -> String -> Either EncodingException WindowsString
- encodeFS :: String -> IO WindowsString
- encodeLE :: String -> IO WindowsString
- fromString :: String -> WindowsString
- fromBytes :: MonadThrow m => ByteString -> m WindowsString
- fromShortBytes :: MonadThrow m => ShortByteString -> m WindowsString
- pstr :: QuasiQuoter
- singleton :: WindowsChar -> WindowsString
- empty :: WindowsString
- pack :: [WindowsChar] -> WindowsString
- decodeUtf :: MonadThrow m => WindowsString -> m String
- decodeWith :: TextEncoding -> WindowsString -> Either EncodingException String
- decodeFS :: WindowsString -> IO String
- decodeLE :: WindowsString -> IO String
- unpack :: WindowsString -> [WindowsChar]
- unsafeFromChar :: Char -> WindowsChar
- toChar :: WindowsChar -> Char
- snoc :: WindowsString -> WindowsChar -> WindowsString
- cons :: WindowsChar -> WindowsString -> WindowsString
- last :: HasCallStack => WindowsString -> WindowsChar
- tail :: HasCallStack => WindowsString -> WindowsString
- uncons :: WindowsString -> Maybe (WindowsChar, WindowsString)
- head :: HasCallStack => WindowsString -> WindowsChar
- init :: HasCallStack => WindowsString -> WindowsString
- unsnoc :: WindowsString -> Maybe (WindowsString, WindowsChar)
- null :: WindowsString -> Bool
- length :: WindowsString -> Int
- lengthBytes :: WindowsString -> Int
- map :: (WindowsChar -> WindowsChar) -> WindowsString -> WindowsString
- reverse :: WindowsString -> WindowsString
- intercalate :: WindowsString -> [WindowsString] -> WindowsString
- foldl :: (a -> WindowsChar -> a) -> a -> WindowsString -> a
- foldl' :: (a -> WindowsChar -> a) -> a -> WindowsString -> a
- foldl1 :: (WindowsChar -> WindowsChar -> WindowsChar) -> WindowsString -> WindowsChar
- foldl1' :: (WindowsChar -> WindowsChar -> WindowsChar) -> WindowsString -> WindowsChar
- foldr :: (WindowsChar -> a -> a) -> a -> WindowsString -> a
- foldr' :: (WindowsChar -> a -> a) -> a -> WindowsString -> a
- foldr1 :: (WindowsChar -> WindowsChar -> WindowsChar) -> WindowsString -> WindowsChar
- foldr1' :: (WindowsChar -> WindowsChar -> WindowsChar) -> WindowsString -> WindowsChar
- all :: (WindowsChar -> Bool) -> WindowsString -> Bool
- any :: (WindowsChar -> Bool) -> WindowsString -> Bool
- concat :: [WindowsString] -> WindowsString
- replicate :: Int -> WindowsChar -> WindowsString
- unfoldr :: (a -> Maybe (WindowsChar, a)) -> a -> WindowsString
- unfoldrN :: Int -> (a -> Maybe (WindowsChar, a)) -> a -> (WindowsString, Maybe a)
- take :: Int -> WindowsString -> WindowsString
- takeEnd :: Int -> WindowsString -> WindowsString
- takeWhileEnd :: (WindowsChar -> Bool) -> WindowsString -> WindowsString
- takeWhile :: (WindowsChar -> Bool) -> WindowsString -> WindowsString
- drop :: Int -> WindowsString -> WindowsString
- dropEnd :: Int -> WindowsString -> WindowsString
- dropWhileEnd :: (WindowsChar -> Bool) -> WindowsString -> WindowsString
- dropWhile :: (WindowsChar -> Bool) -> WindowsString -> WindowsString
- break :: (WindowsChar -> Bool) -> WindowsString -> (WindowsString, WindowsString)
- breakEnd :: (WindowsChar -> Bool) -> WindowsString -> (WindowsString, WindowsString)
- span :: (WindowsChar -> Bool) -> WindowsString -> (WindowsString, WindowsString)
- spanEnd :: (WindowsChar -> Bool) -> WindowsString -> (WindowsString, WindowsString)
- splitAt :: Int -> WindowsString -> (WindowsString, WindowsString)
- split :: WindowsChar -> WindowsString -> [WindowsString]
- splitWith :: (WindowsChar -> Bool) -> WindowsString -> [WindowsString]
- stripSuffix :: WindowsString -> WindowsString -> Maybe WindowsString
- stripPrefix :: WindowsString -> WindowsString -> Maybe WindowsString
- isInfixOf :: WindowsString -> WindowsString -> Bool
- isPrefixOf :: WindowsString -> WindowsString -> Bool
- isSuffixOf :: WindowsString -> WindowsString -> Bool
- breakSubstring :: WindowsString -> WindowsString -> (WindowsString, WindowsString)
- elem :: WindowsChar -> WindowsString -> Bool
- find :: (WindowsChar -> Bool) -> WindowsString -> Maybe WindowsChar
- filter :: (WindowsChar -> Bool) -> WindowsString -> WindowsString
- partition :: (WindowsChar -> Bool) -> WindowsString -> (WindowsString, WindowsString)
- index :: HasCallStack => WindowsString -> Int -> WindowsChar
- indexMaybe :: WindowsString -> Int -> Maybe WindowsChar
- (!?) :: WindowsString -> Int -> Maybe WindowsChar
- elemIndex :: WindowsChar -> WindowsString -> Maybe Int
- elemIndices :: WindowsChar -> WindowsString -> [Int]
- count :: WindowsChar -> WindowsString -> Int
- findIndex :: (WindowsChar -> Bool) -> WindowsString -> Maybe Int
- findIndices :: (WindowsChar -> Bool) -> WindowsString -> [Int]
Types
data WindowsString #
Instances
| Monoid WindowsString | |||||
Defined in System.OsString.Internal.Types.Hidden Methods mappend :: WindowsString -> WindowsString -> WindowsString mconcat :: [WindowsString] -> WindowsString | |||||
| Semigroup WindowsString | |||||
Defined in System.OsString.Internal.Types.Hidden Methods (<>) :: WindowsString -> WindowsString -> WindowsString sconcat :: NonEmpty WindowsString -> WindowsString stimes :: Integral b => b -> WindowsString -> WindowsString | |||||
| Generic WindowsString | |||||
Defined in System.OsString.Internal.Types.Hidden Associated Types
| |||||
| Show WindowsString | |||||
Defined in System.OsString.Internal.Types.Hidden Methods showsPrec :: Int -> WindowsString -> ShowS show :: WindowsString -> String showList :: [WindowsString] -> ShowS | |||||
| NFData WindowsString | |||||
Defined in System.OsString.Internal.Types.Hidden Methods rnf :: WindowsString -> () | |||||
| Eq WindowsString | |||||
Defined in System.OsString.Internal.Types.Hidden | |||||
| Ord WindowsString | |||||
Defined in System.OsString.Internal.Types.Hidden Methods compare :: WindowsString -> WindowsString -> Ordering (<) :: WindowsString -> WindowsString -> Bool (<=) :: WindowsString -> WindowsString -> Bool (>) :: WindowsString -> WindowsString -> Bool (>=) :: WindowsString -> WindowsString -> Bool max :: WindowsString -> WindowsString -> WindowsString min :: WindowsString -> WindowsString -> WindowsString | |||||
| Lift WindowsString | |||||
Defined in System.OsString.Internal.Types.Hidden Methods lift :: Quote m => WindowsString -> m Exp liftTyped :: forall (m :: Type -> Type). Quote m => WindowsString -> Code m WindowsString | |||||
| type Rep WindowsString | |||||
Defined in System.OsString.Internal.Types.Hidden type Rep WindowsString = D1 ('MetaData "WindowsString" "System.OsString.Internal.Types.Hidden" "filepath-1.4.301.0-c27c" 'True) (C1 ('MetaCons "WindowsString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getWindowsString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString))) | |||||
data WindowsChar #
Instances
| Generic WindowsChar | |||||
Defined in System.OsString.Internal.Types.Hidden Associated Types
| |||||
| Show WindowsChar | |||||
Defined in System.OsString.Internal.Types.Hidden Methods showsPrec :: Int -> WindowsChar -> ShowS show :: WindowsChar -> String showList :: [WindowsChar] -> ShowS | |||||
| NFData WindowsChar | |||||
Defined in System.OsString.Internal.Types.Hidden Methods rnf :: WindowsChar -> () | |||||
| Eq WindowsChar | |||||
Defined in System.OsString.Internal.Types.Hidden | |||||
| Ord WindowsChar | |||||
Defined in System.OsString.Internal.Types.Hidden Methods compare :: WindowsChar -> WindowsChar -> Ordering (<) :: WindowsChar -> WindowsChar -> Bool (<=) :: WindowsChar -> WindowsChar -> Bool (>) :: WindowsChar -> WindowsChar -> Bool (>=) :: WindowsChar -> WindowsChar -> Bool max :: WindowsChar -> WindowsChar -> WindowsChar min :: WindowsChar -> WindowsChar -> WindowsChar | |||||
| type Rep WindowsChar | |||||
Defined in System.OsString.Internal.Types.Hidden type Rep WindowsChar = D1 ('MetaData "WindowsChar" "System.OsString.Internal.Types.Hidden" "filepath-1.4.301.0-c27c" 'True) (C1 ('MetaCons "WindowsChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getWindowsChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16))) | |||||
String construction
encodeUtf :: MonadThrow m => String -> m WindowsString Source #
Partial unicode friendly encoding.
This encodes as UTF16-LE (strictly), which is a pretty good guess.
Throws an EncodingException if encoding fails. If the input does not
contain surrogate chars, you can use unsafeEncodeUtf.
unsafeEncodeUtf :: HasCallStack => String -> WindowsString Source #
Unsafe unicode friendly encoding.
Like encodeUtf, except it crashes when the input contains
surrogate chars. For sanitized input, this can be useful.
encodeWith :: TextEncoding -> String -> Either EncodingException WindowsString #
encodeFS :: String -> IO WindowsString Source #
Deprecated: Use System.OsPath.Windows.encodeFS from filepath
This mimics the behavior of the base library when doing filesystem operations (usually filepaths), which does permissive UTF-16 encoding, where coding errors generate Chars in the surrogate range.
The reason this is in IO is because it unifies with the Posix counterpart,
which does require IO. This is safe to unsafePerformIO/unsafeDupablePerformIO.
encodeLE :: String -> IO WindowsString Source #
This mimics the behavior of the base library when doing string operations, which does permissive UTF-16 encoding, where coding errors generate Chars in the surrogate range.
The reason this is in IO is because it unifies with the Posix counterpart,
which does require IO. This is safe to unsafePerformIO/unsafeDupablePerformIO.
fromString :: String -> WindowsString Source #
Like 'encodeLE but not in IO.
encodeLE was designed to have a symmetric type signature
on unix and windows, but morally the function has no IO effects on windows,
so we provide this variant without breaking existing API.
On windows, encodeLE is equivalent to encodeFS.
This function does not exist on unix.
Since: 2.0.6
fromBytes :: MonadThrow m => ByteString -> m WindowsString Source #
Constructs a platform string from a ByteString.
This ensures valid UCS-2LE. Note that this doesn't expand Word8 to Word16 on windows, so you may get invalid UTF-16.
Throws EncodingException on invalid UCS-2LE (although unlikely).
fromShortBytes :: MonadThrow m => ShortByteString -> m WindowsString Source #
Constructs a platform string from a ShortByteString.
This ensures valid UCS-2LE. Note that this doesn't expand Word8 to Word16 on windows, so you may get invalid UTF-16.
Throws EncodingException on invalid UCS-2LE (although unlikely).
Since: 2.0.8
singleton :: WindowsChar -> WindowsString Source #
pack :: [WindowsChar] -> WindowsString Source #
Pack a list of platform words to a platform string.
Note that using this in conjunction with unsafeFromChar to
convert from [Char] to platform string is probably not what
you want, because it will truncate unicode code points.
String deconstruction
decodeUtf :: MonadThrow m => WindowsString -> m String Source #
Partial unicode friendly decoding.
This decodes as UTF16-LE (strictly), which is a pretty good.
Throws a EncodingException if decoding fails.
decodeWith :: TextEncoding -> WindowsString -> Either EncodingException String #
decodeFS :: WindowsString -> IO String Source #
Deprecated: Use System.OsPath.Windows.decodeFS from filepath
Like decodeUtf, except this mimics the behavior of the base library when doing filesystem
operations (usually filepaths), which does permissive UTF-16 encoding, where coding errors generate
Chars in the surrogate range.
The reason this is in IO is because it unifies with the Posix counterpart,
which does require IO. unsafePerformIO/unsafeDupablePerformIO are safe, however.
decodeLE :: WindowsString -> IO String Source #
Like decodeUtf, except this mimics the behavior of the base library when doing filesystem
operations, which does permissive UTF-16 encoding, where coding errors generate
Chars in the surrogate range.
The reason this is in IO is because it unifies with the Posix counterpart,
which does require IO. unsafePerformIO/unsafeDupablePerformIO are safe, however.
unpack :: WindowsString -> [WindowsChar] Source #
Unpack a platform string to a list of platform words.
Word construction
unsafeFromChar :: Char -> WindowsChar Source #
Truncates to 2 octets.
Word deconstruction
toChar :: WindowsChar -> Char Source #
Converts back to a unicode codepoint (total).
Basic interface
snoc :: WindowsString -> WindowsChar -> WindowsString Source #
O(n) Append a byte to the end of a WindowsString
cons :: WindowsChar -> WindowsString -> WindowsString Source #
O(n) cons is analogous to (:) for lists.
last :: HasCallStack => WindowsString -> WindowsChar Source #
O(1) Extract the last element of a WindowsString, which must be finite and non-empty.
An exception will be thrown in the case of an empty WindowsString.
This is a partial function, consider using unsnoc instead.
tail :: HasCallStack => WindowsString -> WindowsString Source #
O(n) Extract the elements after the head of a WindowsString, which must be non-empty.
An exception will be thrown in the case of an empty WindowsString.
This is a partial function, consider using uncons instead.
uncons :: WindowsString -> Maybe (WindowsChar, WindowsString) Source #
O(n) Extract the head and tail of a WindowsString, returning Nothing
if it is empty.
head :: HasCallStack => WindowsString -> WindowsChar Source #
O(1) Extract the first element of a WindowsString, which must be non-empty.
An exception will be thrown in the case of an empty WindowsString.
This is a partial function, consider using uncons instead.
init :: HasCallStack => WindowsString -> WindowsString Source #
O(n) Return all the elements of a WindowsString except the last one.
An exception will be thrown in the case of an empty WindowsString.
This is a partial function, consider using unsnoc instead.
unsnoc :: WindowsString -> Maybe (WindowsString, WindowsChar) Source #
O(n) Extract the init and last of a WindowsString, returning Nothing
if it is empty.
null :: WindowsString -> Bool Source #
O(1). The empty WindowsString.
length :: WindowsString -> Int Source #
O(1) The length of a WindowsString.
This returns the number of code units
(Word8 on unix and Word16 on windows), not
bytes.
>>>length "abc"3
Note: older versions of os-string return the
length in bytes, rather than the length in
code units. This will return the length in
code units, regardless of the version of
os-string. For checking the length in Bytes,
use lengthBytes.
lengthBytes :: WindowsString -> Int Source #
O(1) The length in bytes of a WindowsString.
If you want the number of code units, just
use length instead.
Transforming WindowsStrings
map :: (WindowsChar -> WindowsChar) -> WindowsString -> WindowsString Source #
O(n) map f xs is the WindowsString obtained by applying f to each
element of xs.
reverse :: WindowsString -> WindowsString Source #
O(n) reverse xs efficiently returns the elements of xs in reverse order.
intercalate :: WindowsString -> [WindowsString] -> WindowsString Source #
O(n) The intercalate function takes a WindowsString and a list of
WindowsStrings and concatenates the list after interspersing the first
argument between each element of the list.
Reducing WindowsStrings (folds)
foldl :: (a -> WindowsChar -> a) -> a -> WindowsString -> a Source #
foldl, applied to a binary operator, a starting value (typically
the left-identity of the operator), and a WindowsString, reduces the
WindowsString using the binary operator, from left to right.
foldl' :: (a -> WindowsChar -> a) -> a -> WindowsString -> a Source #
foldl1 :: (WindowsChar -> WindowsChar -> WindowsChar) -> WindowsString -> WindowsChar Source #
foldl1 is a variant of foldl that has no starting value
argument, and thus must be applied to non-empty WindowsStrings.
An exception will be thrown in the case of an empty WindowsString.
foldl1' :: (WindowsChar -> WindowsChar -> WindowsChar) -> WindowsString -> WindowsChar Source #
foldl1' is like foldl1, but strict in the accumulator.
An exception will be thrown in the case of an empty WindowsString.
foldr :: (WindowsChar -> a -> a) -> a -> WindowsString -> a Source #
foldr, applied to a binary operator, a starting value
(typically the right-identity of the operator), and a WindowsString,
reduces the WindowsString using the binary operator, from right to left.
foldr' :: (WindowsChar -> a -> a) -> a -> WindowsString -> a Source #
foldr1 :: (WindowsChar -> WindowsChar -> WindowsChar) -> WindowsString -> WindowsChar Source #
foldr1 is a variant of foldr that has no starting value argument,
and thus must be applied to non-empty WindowsStrings
An exception will be thrown in the case of an empty WindowsString.
foldr1' :: (WindowsChar -> WindowsChar -> WindowsChar) -> WindowsString -> WindowsChar Source #
Special folds
all :: (WindowsChar -> Bool) -> WindowsString -> Bool Source #
O(n) Applied to a predicate and a PLATFString, all determines
if all elements of the WindowsString satisfy the predicate.
any :: (WindowsChar -> Bool) -> WindowsString -> Bool Source #
O(n) Applied to a predicate and a WindowsString, any determines if
any element of the WindowsString satisfies the predicate.
concat :: [WindowsString] -> WindowsString Source #
Generating and unfolding WindowsStrings
replicate :: Int -> WindowsChar -> WindowsString Source #
O(n) replicate n x is a WindowsString of length n with x
the value of every element. The following holds:
replicate w c = unfoldr w (\u -> Just (u,u)) c
unfoldr :: (a -> Maybe (WindowsChar, a)) -> a -> WindowsString Source #
O(n), where n is the length of the result. The unfoldr
function is analogous to the List 'unfoldr'. unfoldr builds a
WindowsString from a seed value. The function takes the element and
returns Nothing if it is done producing the WindowsString or returns
Just (a,b), in which case, a is the next byte in the string,
and b is the seed value for further production.
This function is not efficient/safe. It will build a list of [Word8]
and run the generator until it returns Nothing, otherwise recurse infinitely,
then finally create a WindowsString.
If you know the maximum length, consider using unfoldrN.
Examples:
unfoldr (\x -> if x <= 5 then Just (x, x + 1) else Nothing) 0 == pack [0, 1, 2, 3, 4, 5]
unfoldrN :: Int -> (a -> Maybe (WindowsChar, a)) -> a -> (WindowsString, Maybe a) Source #
O(n) Like unfoldr, unfoldrN builds a WindowsString from a seed
value. However, the length of the result is limited by the first
argument to unfoldrN. This function is more efficient than unfoldr
when the maximum length of the result is known.
The following equation relates unfoldrN and unfoldr:
fst (unfoldrN n f s) == take n (unfoldr f s)
Substrings
Breaking strings
take :: Int -> WindowsString -> WindowsString Source #
O(n) take n, applied to a WindowsString xs, returns the prefix
of xs of length n, or xs itself if n > .length xs
takeEnd :: Int -> WindowsString -> WindowsString Source #
takeWhileEnd :: (WindowsChar -> Bool) -> WindowsString -> WindowsString Source #
Returns the longest (possibly empty) suffix of elements satisfying the predicate.
is equivalent to takeWhileEnd p.reverse . takeWhile p . reverse
takeWhile :: (WindowsChar -> Bool) -> WindowsString -> WindowsString Source #
Similar to takeWhile,
returns the longest (possibly empty) prefix of elements
satisfying the predicate.
drop :: Int -> WindowsString -> WindowsString Source #
dropEnd :: Int -> WindowsString -> WindowsString Source #
dropWhileEnd :: (WindowsChar -> Bool) -> WindowsString -> WindowsString Source #
Similar to dropWhileEnd,
drops the longest (possibly empty) suffix of elements
satisfying the predicate and returns the remainder.
is equivalent to dropWhileEnd p.reverse . dropWhile p . reverse
dropWhile :: (WindowsChar -> Bool) -> WindowsString -> WindowsString Source #
Similar to dropWhile,
drops the longest (possibly empty) prefix of elements
satisfying the predicate and returns the remainder.
break :: (WindowsChar -> Bool) -> WindowsString -> (WindowsString, WindowsString) Source #
breakEnd :: (WindowsChar -> Bool) -> WindowsString -> (WindowsString, WindowsString) Source #
Returns the longest (possibly empty) suffix of elements which do not satisfy the predicate and the remainder of the string.
breakEnd p is equivalent to and to spanEnd (not . p)(.takeWhileEnd (not . p) &&& dropWhileEnd (not . p))
span :: (WindowsChar -> Bool) -> WindowsString -> (WindowsString, WindowsString) Source #
spanEnd :: (WindowsChar -> Bool) -> WindowsString -> (WindowsString, WindowsString) Source #
Returns the longest (possibly empty) suffix of elements satisfying the predicate and the remainder of the string.
spanEnd p is equivalent to and to breakEnd (not . p)(.takeWhileEnd p &&& dropWhileEnd p)
We have
spanEnd (not . isSpace) "x y z" == ("x y ", "z")and
spanEnd (not . isSpace) sbs == let (x, y) = span (not . isSpace) (reverse sbs) in (reverse y, reverse x)
splitAt :: Int -> WindowsString -> (WindowsString, WindowsString) Source #
split :: WindowsChar -> WindowsString -> [WindowsString] Source #
O(n) Break a WindowsString into pieces separated by the byte
argument, consuming the delimiter. I.e.
split 10 "a\nb\nd\ne" == ["a","b","d","e"] -- fromEnum '\n' == 10 split 97 "aXaXaXa" == ["","X","X","X",""] -- fromEnum 'a' == 97 split 120 "x" == ["",""] -- fromEnum 'x' == 120 split undefined "" == [] -- and not [""]
and
intercalate [c] . split c == id split == splitWith . (==)
splitWith :: (WindowsChar -> Bool) -> WindowsString -> [WindowsString] Source #
O(n) Splits a WindowsString 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. eg.
splitWith (==97) "aabbaca" == ["","","bb","c",""] -- fromEnum 'a' == 97 splitWith undefined "" == [] -- and not [""]
stripSuffix :: WindowsString -> WindowsString -> Maybe WindowsString Source #
O(n) The stripSuffix function takes two OsStrings and returns Just
the remainder of the second iff the first is its suffix, and otherwise
Nothing.
stripPrefix :: WindowsString -> WindowsString -> Maybe WindowsString Source #
O(n) The stripPrefix function takes two OsStrings and returns Just
the remainder of the second iff the first is its prefix, and otherwise
Nothing.
Predicates
isInfixOf :: WindowsString -> WindowsString -> Bool Source #
Check whether one string is a substring of another.
isPrefixOf :: WindowsString -> WindowsString -> Bool Source #
O(n) The isPrefixOf function takes two OsStrings and returns True
isSuffixOf :: WindowsString -> WindowsString -> Bool Source #
O(n) The isSuffixOf function takes two OsStrings and returns True
iff the first is a suffix of the second.
The following holds:
isSuffixOf x y == reverse x `isPrefixOf` reverse y
Search for arbitrary susbstrings
breakSubstring :: WindowsString -> WindowsString -> (WindowsString, WindowsString) Source #
Break a string on a substring, returning a pair of the part of the string prior to the match, and the rest of the string.
The following relationships hold:
break (== c) l == breakSubstring (singleton c) l
For example, to tokenise a string, dropping delimiters:
tokenise x y = h : if null t then [] else tokenise x (drop (length x) t)
where (h,t) = breakSubstring x yTo skip to the first occurrence of a string:
snd (breakSubstring x y)
To take the parts of a string before a delimiter:
fst (breakSubstring x y)
Note that calling `breakSubstring x` does some preprocessing work, so you should avoid unnecessarily duplicating breakSubstring calls with the same pattern.
Searching WindowsStrings
Searching by equality
elem :: WindowsChar -> WindowsString -> Bool Source #
O(n) elem is the WindowsString membership predicate.
find :: (WindowsChar -> Bool) -> WindowsString -> Maybe WindowsChar Source #
O(n) The find function takes a predicate and a WindowsString,
and returns the first element in matching the predicate, or Nothing
if there is no such element.
find f p = case findIndex f p of Just n -> Just (p ! n) ; _ -> Nothing
filter :: (WindowsChar -> Bool) -> WindowsString -> WindowsString Source #
O(n) filter, applied to a predicate and a WindowsString,
returns a WindowsString containing those characters that satisfy the
predicate.
partition :: (WindowsChar -> Bool) -> WindowsString -> (WindowsString, WindowsString) Source #
O(n) The partition function takes a predicate a WindowsString and returns
the pair of OsStrings with elements which do and do not satisfy the
predicate, respectively; i.e.,
partition p bs == (filter p sbs, filter (not . p) sbs)
Indexing WindowsStrings
index :: HasCallStack => WindowsString -> Int -> WindowsChar Source #
O(1) WindowsString index (subscript) operator, starting from 0.
indexMaybe :: WindowsString -> Int -> Maybe WindowsChar Source #
O(1) WindowsString index, starting from 0, that returns Just if:
0 <= n < length bs
(!?) :: WindowsString -> Int -> Maybe WindowsChar Source #
O(1) WindowsString index, starting from 0, that returns Just if:
0 <= n < length bs
elemIndex :: WindowsChar -> WindowsString -> Maybe Int Source #
O(n) The elemIndex function returns the index of the first
element in the given WindowsString which is equal to the query
element, or Nothing if there is no such element.
elemIndices :: WindowsChar -> WindowsString -> [Int] Source #
O(n) The elemIndices function extends elemIndex, by returning
the indices of all elements equal to the query element, in ascending order.
count :: WindowsChar -> WindowsString -> Int Source #
count returns the number of times its argument appears in the WindowsString
findIndex :: (WindowsChar -> Bool) -> WindowsString -> Maybe Int Source #
O(n) The findIndex function takes a predicate and a WindowsString and
returns the index of the first element in the WindowsString
satisfying the predicate.
findIndices :: (WindowsChar -> Bool) -> WindowsString -> [Int] Source #
O(n) The findIndices function extends findIndex, by returning the
indices of all elements satisfying the predicate, in ascending order.