Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data PosixString
- data PosixChar
- encodeUtf :: MonadThrow m => String -> m PosixString
- unsafeEncodeUtf :: HasCallStack => String -> PosixString
- encodeWith :: TextEncoding -> String -> Either EncodingException PosixString
- encodeFS :: String -> IO PosixString
- fromBytes :: MonadThrow m => ByteString -> m PosixString
- pstr :: QuasiQuoter
- singleton :: PosixChar -> PosixString
- empty :: PosixString
- pack :: [PosixChar] -> PosixString
- decodeUtf :: MonadThrow m => PosixString -> m String
- decodeWith :: TextEncoding -> PosixString -> Either EncodingException String
- decodeFS :: PosixString -> IO String
- unpack :: PosixString -> [PosixChar]
- unsafeFromChar :: Char -> PosixChar
- toChar :: PosixChar -> Char
- snoc :: PosixString -> PosixChar -> PosixString
- cons :: PosixChar -> PosixString -> PosixString
- last :: HasCallStack => PosixString -> PosixChar
- tail :: HasCallStack => PosixString -> PosixString
- uncons :: PosixString -> Maybe (PosixChar, PosixString)
- head :: HasCallStack => PosixString -> PosixChar
- init :: HasCallStack => PosixString -> PosixString
- unsnoc :: PosixString -> Maybe (PosixString, PosixChar)
- null :: PosixString -> Bool
- length :: PosixString -> Int
- map :: (PosixChar -> PosixChar) -> PosixString -> PosixString
- reverse :: PosixString -> PosixString
- intercalate :: PosixString -> [PosixString] -> PosixString
- foldl :: forall a. (a -> PosixChar -> a) -> a -> PosixString -> a
- foldl' :: forall a. (a -> PosixChar -> a) -> a -> PosixString -> a
- foldl1 :: (PosixChar -> PosixChar -> PosixChar) -> PosixString -> PosixChar
- foldl1' :: (PosixChar -> PosixChar -> PosixChar) -> PosixString -> PosixChar
- foldr :: forall a. (PosixChar -> a -> a) -> a -> PosixString -> a
- foldr' :: forall a. (PosixChar -> a -> a) -> a -> PosixString -> a
- foldr1 :: (PosixChar -> PosixChar -> PosixChar) -> PosixString -> PosixChar
- foldr1' :: (PosixChar -> PosixChar -> PosixChar) -> PosixString -> PosixChar
- all :: (PosixChar -> Bool) -> PosixString -> Bool
- any :: (PosixChar -> Bool) -> PosixString -> Bool
- concat :: [PosixString] -> PosixString
- replicate :: Int -> PosixChar -> PosixString
- unfoldr :: forall a. (a -> Maybe (PosixChar, a)) -> a -> PosixString
- unfoldrN :: forall a. Int -> (a -> Maybe (PosixChar, a)) -> a -> (PosixString, Maybe a)
- take :: Int -> PosixString -> PosixString
- takeEnd :: Int -> PosixString -> PosixString
- takeWhileEnd :: (PosixChar -> Bool) -> PosixString -> PosixString
- takeWhile :: (PosixChar -> Bool) -> PosixString -> PosixString
- drop :: Int -> PosixString -> PosixString
- dropEnd :: Int -> PosixString -> PosixString
- dropWhileEnd :: (PosixChar -> Bool) -> PosixString -> PosixString
- dropWhile :: (PosixChar -> Bool) -> PosixString -> PosixString
- break :: (PosixChar -> Bool) -> PosixString -> (PosixString, PosixString)
- breakEnd :: (PosixChar -> Bool) -> PosixString -> (PosixString, PosixString)
- span :: (PosixChar -> Bool) -> PosixString -> (PosixString, PosixString)
- spanEnd :: (PosixChar -> Bool) -> PosixString -> (PosixString, PosixString)
- splitAt :: Int -> PosixString -> (PosixString, PosixString)
- split :: PosixChar -> PosixString -> [PosixString]
- splitWith :: (PosixChar -> Bool) -> PosixString -> [PosixString]
- stripSuffix :: PosixString -> PosixString -> Maybe PosixString
- stripPrefix :: PosixString -> PosixString -> Maybe PosixString
- isInfixOf :: PosixString -> PosixString -> Bool
- isPrefixOf :: PosixString -> PosixString -> Bool
- isSuffixOf :: PosixString -> PosixString -> Bool
- breakSubstring :: PosixString -> PosixString -> (PosixString, PosixString)
- elem :: PosixChar -> PosixString -> Bool
- find :: (PosixChar -> Bool) -> PosixString -> Maybe PosixChar
- filter :: (PosixChar -> Bool) -> PosixString -> PosixString
- partition :: (PosixChar -> Bool) -> PosixString -> (PosixString, PosixString)
- index :: HasCallStack => PosixString -> Int -> PosixChar
- indexMaybe :: PosixString -> Int -> Maybe PosixChar
- (!?) :: PosixString -> Int -> Maybe PosixChar
- elemIndex :: PosixChar -> PosixString -> Maybe Int
- elemIndices :: PosixChar -> PosixString -> [Int]
- count :: PosixChar -> PosixString -> Int
- findIndex :: (PosixChar -> Bool) -> PosixString -> Maybe Int
- findIndices :: (PosixChar -> Bool) -> PosixString -> [Int]
Types
data PosixString Source #
Commonly used Posix string as uninterpreted char[]
array.
Instances
String construction
encodeUtf :: MonadThrow m => String -> m PosixString Source #
Partial unicode friendly encoding.
This encodes as UTF8 (strictly), which is a good guess.
Throws an EncodingException
if encoding fails. If the input does not
contain surrogate chars, you can use unsafeEncodeUtf
.
unsafeEncodeUtf :: HasCallStack => String -> PosixString 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 PosixString Source #
Encode a String
with the specified encoding.
encodeFS :: String -> IO PosixString Source #
This mimics the behavior of the base library when doing filesystem operations, which uses shady PEP 383 style encoding (based on the current locale, but PEP 383 only works properly on UTF-8 encodings, so good luck).
Looking up the locale requires IO. If you're not worried about calls
to setFileSystemEncoding
, then unsafePerformIO
may be feasible (make sure
to deeply evaluate the result to catch exceptions).
fromBytes :: MonadThrow m => ByteString -> m PosixString Source #
Constructs a platform string from a ByteString.
This is a no-op.
pstr :: QuasiQuoter Source #
QuasiQuote a PosixString
. This accepts Unicode characters
and encodes as UTF-8 on unix.
singleton :: PosixChar -> PosixString Source #
empty :: PosixString Source #
pack :: [PosixChar] -> PosixString 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 => PosixString -> m String Source #
Partial unicode friendly decoding.
This decodes as UTF8 (strictly), which is a good guess. Note that filenames on unix are encoding agnostic char arrays.
Throws a EncodingException
if decoding fails.
decodeWith :: TextEncoding -> PosixString -> Either EncodingException String Source #
Decode a PosixString
with the specified encoding.
The String is forced into memory to catch all exceptions.
decodeFS :: PosixString -> IO String Source #
This mimics the behavior of the base library when doing filesystem operations, which uses shady PEP 383 style encoding (based on the current locale, but PEP 383 only works properly on UTF-8 encodings, so good luck).
Looking up the locale requires IO. If you're not worried about calls
to setFileSystemEncoding
, then unsafePerformIO
may be feasible (make sure
to deeply evaluate the result to catch exceptions).
unpack :: PosixString -> [PosixChar] Source #
Unpack a platform string to a list of platform words.
Word construction
unsafeFromChar :: Char -> PosixChar Source #
Truncates to 1 octet.
Word deconstruction
Basic interface
snoc :: PosixString -> PosixChar -> PosixString Source #
O(n) Append a byte to the end of a OsString
Since: 1.4.200.0
cons :: PosixChar -> PosixString -> PosixString Source #
O(n) cons
is analogous to (:) for lists.
Since: 1.4.200.0
last :: HasCallStack => PosixString -> PosixChar Source #
O(1) Extract the last element of a OsString, which must be finite and non-empty. An exception will be thrown in the case of an empty OsString.
This is a partial function, consider using unsnoc
instead.
Since: 1.4.200.0
tail :: HasCallStack => PosixString -> PosixString Source #
O(n) Extract the elements after the head of a OsString, which must be non-empty. An exception will be thrown in the case of an empty OsString.
This is a partial function, consider using uncons
instead.
Since: 1.4.200.0
uncons :: PosixString -> Maybe (PosixChar, PosixString) Source #
head :: HasCallStack => PosixString -> PosixChar Source #
O(1) Extract the first element of a OsString, which must be non-empty. An exception will be thrown in the case of an empty OsString.
This is a partial function, consider using uncons
instead.
Since: 1.4.200.0
init :: HasCallStack => PosixString -> PosixString Source #
O(n) Return all the elements of a OsString
except the last one.
An exception will be thrown in the case of an empty OsString.
This is a partial function, consider using unsnoc
instead.
Since: 1.4.200.0
unsnoc :: PosixString -> Maybe (PosixString, PosixChar) Source #
null :: PosixString -> Bool Source #
O(1). The empty OsString
.
Since: 1.4.200.0
length :: PosixString -> Int Source #
O(1) The length of a OsString
.
Since: 1.4.200.0
Transforming OsString
map :: (PosixChar -> PosixChar) -> PosixString -> PosixString Source #
O(n) map
f xs
is the OsString obtained by applying f
to each
element of xs
.
Since: 1.4.200.0
reverse :: PosixString -> PosixString Source #
O(n) reverse
xs
efficiently returns the elements of xs
in reverse order.
Since: 1.4.200.0
intercalate :: PosixString -> [PosixString] -> PosixString Source #
O(n) The intercalate
function takes a OsString
and a list of
OsString
s and concatenates the list after interspersing the first
argument between each element of the list.
Since: 1.4.200.0
Reducing OsStrings (folds)
foldl :: forall a. (a -> PosixChar -> a) -> a -> PosixString -> a Source #
foldl
, applied to a binary operator, a starting value (typically
the left-identity of the operator), and a OsString, reduces the
OsString using the binary operator, from left to right.
Since: 1.4.200.0
foldl' :: forall a. (a -> PosixChar -> a) -> a -> PosixString -> a Source #
foldr :: forall a. (PosixChar -> a -> a) -> a -> PosixString -> a Source #
foldr
, applied to a binary operator, a starting value
(typically the right-identity of the operator), and a OsString,
reduces the OsString using the binary operator, from right to left.
Since: 1.4.200.0
foldr' :: forall a. (PosixChar -> a -> a) -> a -> PosixString -> a Source #
Special folds
all :: (PosixChar -> Bool) -> PosixString -> Bool Source #
O(n) Applied to a predicate and a OsString
, all
determines
if all elements of the OsString
satisfy the predicate.
Since: 1.4.200.0
any :: (PosixChar -> Bool) -> PosixString -> Bool Source #
O(n) Applied to a predicate and a OsString
, any
determines if
any element of the OsString
satisfies the predicate.
Since: 1.4.200.0
concat :: [PosixString] -> PosixString Source #
Generating and unfolding OsStrings
replicate :: Int -> PosixChar -> PosixString Source #
O(n) replicate
n x
is a OsString of length n
with x
the value of every element. The following holds:
replicate w c = unfoldr w (\u -> Just (u,u)) c
Since: 1.4.200.0
unfoldr :: forall a. (a -> Maybe (PosixChar, a)) -> a -> PosixString Source #
O(n), where n is the length of the result. The unfoldr
function is analogous to the List 'unfoldr'. unfoldr
builds a
OsString from a seed value. The function takes the element and
returns Nothing
if it is done producing the OsString 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 OsString
.
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]
Since: 1.4.200.0
unfoldrN :: forall a. Int -> (a -> Maybe (PosixChar, a)) -> a -> (PosixString, Maybe a) Source #
O(n) Like unfoldr
, unfoldrN
builds a OsString 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)
Since: 1.4.200.0
Substrings
Breaking strings
take :: Int -> PosixString -> PosixString Source #
takeEnd :: Int -> PosixString -> PosixString Source #
takeWhileEnd :: (PosixChar -> Bool) -> PosixString -> PosixString Source #
Returns the longest (possibly empty) suffix of elements satisfying the predicate.
is equivalent to takeWhileEnd
p
.reverse
. takeWhile
p . reverse
Since: 1.4.200.0
takeWhile :: (PosixChar -> Bool) -> PosixString -> PosixString Source #
Similar to takeWhile
,
returns the longest (possibly empty) prefix of elements
satisfying the predicate.
Since: 1.4.200.0
drop :: Int -> PosixString -> PosixString Source #
dropEnd :: Int -> PosixString -> PosixString Source #
dropWhileEnd :: (PosixChar -> Bool) -> PosixString -> PosixString 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
Since: 1.4.200.0
dropWhile :: (PosixChar -> Bool) -> PosixString -> PosixString Source #
Similar to dropWhile
,
drops the longest (possibly empty) prefix of elements
satisfying the predicate and returns the remainder.
Since: 1.4.200.0
break :: (PosixChar -> Bool) -> PosixString -> (PosixString, PosixString) Source #
breakEnd :: (PosixChar -> Bool) -> PosixString -> (PosixString, PosixString) 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))
Since: 1.4.200.0
span :: (PosixChar -> Bool) -> PosixString -> (PosixString, PosixString) Source #
spanEnd :: (PosixChar -> Bool) -> PosixString -> (PosixString, PosixString) 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)
Since: 1.4.200.0
splitAt :: Int -> PosixString -> (PosixString, PosixString) Source #
split :: PosixChar -> PosixString -> [PosixString] Source #
O(n) Break a OsString
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 . (==)
Since: 1.4.200.0
splitWith :: (PosixChar -> Bool) -> PosixString -> [PosixString] Source #
O(n) Splits a OsString
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 [""]
Since: 1.4.200.0
stripSuffix :: PosixString -> PosixString -> Maybe PosixString 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
.
Since: 1.4.200.0
stripPrefix :: PosixString -> PosixString -> Maybe PosixString 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
.
Since: 1.4.200.0
Predicates
isInfixOf :: PosixString -> PosixString -> Bool Source #
Check whether one string is a substring of another.
Since: 1.4.200.0
isPrefixOf :: PosixString -> PosixString -> Bool Source #
O(n) The isPrefixOf
function takes two OsStrings and returns True
Since: 1.4.200.0
isSuffixOf :: PosixString -> PosixString -> 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
Since: 1.4.200.0
Search for arbitrary susbstrings
breakSubstring :: PosixString -> PosixString -> (PosixString, PosixString) 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 y
To 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.
Since: 1.4.200.0
Searching OsStrings
Searching by equality
elem :: PosixChar -> PosixString -> Bool Source #
O(n) elem
is the OsString
membership predicate.
Since: 1.4.200.0
filter :: (PosixChar -> Bool) -> PosixString -> PosixString Source #
O(n) filter
, applied to a predicate and a OsString,
returns a OsString containing those characters that satisfy the
predicate.
Since: 1.4.200.0
partition :: (PosixChar -> Bool) -> PosixString -> (PosixString, PosixString) Source #
O(n) The partition
function takes a predicate a OsString 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)
Since: 1.4.200.0
Indexing OsStrings
index :: HasCallStack => PosixString -> Int -> PosixChar Source #
O(1) OsString
index (subscript) operator, starting from 0.
Since: 1.4.200.0
indexMaybe :: PosixString -> Int -> Maybe PosixChar Source #
elemIndices :: PosixChar -> PosixString -> [Int] Source #
O(n) The elemIndices
function extends elemIndex
, by returning
the indices of all elements equal to the query element, in ascending order.
Since: 1.4.200.0
count :: PosixChar -> PosixString -> Int Source #
count returns the number of times its argument appears in the OsString
Since: 1.4.200.0
findIndex :: (PosixChar -> Bool) -> PosixString -> Maybe Int Source #
O(n) The findIndex
function takes a predicate and a OsString
and
returns the index of the first element in the OsString
satisfying the predicate.
Since: 1.4.200.0
findIndices :: (PosixChar -> Bool) -> PosixString -> [Int] Source #
O(n) The findIndices
function extends findIndex
, by returning the
indices of all elements satisfying the predicate, in ascending order.
Since: 1.4.200.0