Copyright | © 2022 Julian Ospald |
---|---|
License | MIT |
Maintainer | Julian Ospald <hasufell@posteo.de> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
ShortByteStrings encoded as UTF16-LE, suitable for windows FFI calls.
Word16s are *always* in BE encoding (both input and output), so e.g. pack
takes a list of BE encoded [Word16]
and produces a UTF16-LE encoded ShortByteString.
Likewise, unpack
takes a UTF16-LE encoded ShortByteString and produces a list of BE encoded [Word16]
.
Indices and lengths are always in respect to Word16, not Word8.
All functions will error out if the input string is not a valid UTF16 stream (uneven number of bytes). So use this module with caution.
Synopsis
- data ShortByteString = SBS ByteArray#
- empty :: ShortByteString
- singleton :: Word16 -> ShortByteString
- pack :: [Word16] -> ShortByteString
- unpack :: ShortByteString -> [Word16]
- fromShort :: ShortByteString -> ByteString
- toShort :: ByteString -> ShortByteString
- snoc :: ShortByteString -> Word16 -> ShortByteString
- cons :: Word16 -> ShortByteString -> ShortByteString
- append :: ShortByteString -> ShortByteString -> ShortByteString
- last :: HasCallStack => ShortByteString -> Word16
- tail :: HasCallStack => ShortByteString -> ShortByteString
- uncons :: ShortByteString -> Maybe (Word16, ShortByteString)
- uncons2 :: ShortByteString -> Maybe (Word16, Word16, ShortByteString)
- head :: HasCallStack => ShortByteString -> Word16
- init :: HasCallStack => ShortByteString -> ShortByteString
- unsnoc :: ShortByteString -> Maybe (ShortByteString, Word16)
- null :: ShortByteString -> Bool
- length :: ShortByteString -> Int
- numWord16 :: ShortByteString -> Int
- map :: (Word16 -> Word16) -> ShortByteString -> ShortByteString
- reverse :: ShortByteString -> ShortByteString
- intercalate :: ShortByteString -> [ShortByteString] -> ShortByteString
- foldl :: (a -> Word16 -> a) -> a -> ShortByteString -> a
- foldl' :: (a -> Word16 -> a) -> a -> ShortByteString -> a
- foldl1 :: HasCallStack => (Word16 -> Word16 -> Word16) -> ShortByteString -> Word16
- foldl1' :: HasCallStack => (Word16 -> Word16 -> Word16) -> ShortByteString -> Word16
- foldr :: (Word16 -> a -> a) -> a -> ShortByteString -> a
- foldr' :: (Word16 -> a -> a) -> a -> ShortByteString -> a
- foldr1 :: HasCallStack => (Word16 -> Word16 -> Word16) -> ShortByteString -> Word16
- foldr1' :: HasCallStack => (Word16 -> Word16 -> Word16) -> ShortByteString -> Word16
- all :: (Word16 -> Bool) -> ShortByteString -> Bool
- any :: (Word16 -> Bool) -> ShortByteString -> Bool
- concat :: [ShortByteString] -> ShortByteString
- replicate :: Int -> Word16 -> ShortByteString
- unfoldr :: (a -> Maybe (Word16, a)) -> a -> ShortByteString
- unfoldrN :: forall a. Int -> (a -> Maybe (Word16, a)) -> a -> (ShortByteString, Maybe a)
- take :: Int -> ShortByteString -> ShortByteString
- takeEnd :: Int -> ShortByteString -> ShortByteString
- takeWhileEnd :: (Word16 -> Bool) -> ShortByteString -> ShortByteString
- takeWhile :: (Word16 -> Bool) -> ShortByteString -> ShortByteString
- drop :: Int -> ShortByteString -> ShortByteString
- dropEnd :: Int -> ShortByteString -> ShortByteString
- dropWhile :: (Word16 -> Bool) -> ShortByteString -> ShortByteString
- dropWhileEnd :: (Word16 -> Bool) -> ShortByteString -> ShortByteString
- breakEnd :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
- break :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
- span :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
- spanEnd :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
- splitAt :: Int -> ShortByteString -> (ShortByteString, ShortByteString)
- split :: Word16 -> ShortByteString -> [ShortByteString]
- splitWith :: (Word16 -> Bool) -> ShortByteString -> [ShortByteString]
- stripSuffix :: ShortByteString -> ShortByteString -> Maybe ShortByteString
- stripPrefix :: ShortByteString -> ShortByteString -> Maybe ShortByteString
- isInfixOf :: ShortByteString -> ShortByteString -> Bool
- isPrefixOf :: ShortByteString -> ShortByteString -> Bool
- isSuffixOf :: ShortByteString -> ShortByteString -> Bool
- breakSubstring :: ShortByteString -> ShortByteString -> (ShortByteString, ShortByteString)
- elem :: Word16 -> ShortByteString -> Bool
- find :: (Word16 -> Bool) -> ShortByteString -> Maybe Word16
- filter :: (Word16 -> Bool) -> ShortByteString -> ShortByteString
- partition :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
- index :: HasCallStack => ShortByteString -> Int -> Word16
- indexMaybe :: ShortByteString -> Int -> Maybe Word16
- (!?) :: ShortByteString -> Int -> Maybe Word16
- elemIndex :: Word16 -> ShortByteString -> Maybe Int
- elemIndices :: Word16 -> ShortByteString -> [Int]
- count :: Word16 -> ShortByteString -> Int
- findIndex :: (Word16 -> Bool) -> ShortByteString -> Maybe Int
- findIndices :: (Word16 -> Bool) -> ShortByteString -> [Int]
- packCWString :: Ptr Word16 -> IO ShortByteString
- packCWStringLen :: (Ptr Word16, Int) -> IO ShortByteString
- newCWString :: ShortByteString -> IO (Ptr Word16)
- useAsCWString :: ShortByteString -> (Ptr Word16 -> IO a) -> IO a
- useAsCWStringLen :: ShortByteString -> ((Ptr Word16, Int) -> IO a) -> IO a
The ShortByteString
type and representation
data ShortByteString Source #
A compact representation of a Word8
vector.
It has a lower memory overhead than a ByteString
and does not
contribute to heap fragmentation. It can be converted to or from a
ByteString
(at the cost of copying the string data). It supports very few
other operations.
Instances
Introducing and eliminating ShortByteString
s
empty :: ShortByteString Source #
O(1). The empty ShortByteString
.
singleton :: Word16 -> ShortByteString Source #
O(1) Convert a Word16
into a ShortByteString
pack :: [Word16] -> ShortByteString Source #
O(n). Convert a list into a ShortByteString
unpack :: ShortByteString -> [Word16] Source #
O(n). Convert a ShortByteString
into a list.
fromShort :: ShortByteString -> ByteString Source #
O(n). Convert a ShortByteString
into a ByteString
.
toShort :: ByteString -> ShortByteString Source #
O(n). Convert a ByteString
into a ShortByteString
.
This makes a copy, so does not retain the input string.
Basic interface
snoc :: ShortByteString -> Word16 -> ShortByteString infixl 5 Source #
O(n) Append a Word16 to the end of a ShortByteString
Note: copies the entire byte array
cons :: Word16 -> ShortByteString -> ShortByteString infixr 5 Source #
O(n) cons
is analogous to (:) for lists.
Note: copies the entire byte array
last :: HasCallStack => ShortByteString -> Word16 Source #
O(1) Extract the last element of a ShortByteString, which must be finite and at least one Word16. An exception will be thrown in the case of an empty ShortByteString.
tail :: HasCallStack => ShortByteString -> ShortByteString Source #
O(n) Extract the elements after the head of a ShortByteString, which must at least one Word16. An exception will be thrown in the case of an empty ShortByteString.
Note: copies the entire byte array
uncons :: ShortByteString -> Maybe (Word16, ShortByteString) Source #
O(n) Extract the head and tail of a ByteString, returning Nothing if it is empty.
uncons2 :: ShortByteString -> Maybe (Word16, Word16, ShortByteString) Source #
O(n) Extract first two elements and the rest of a ByteString, returning Nothing if it is shorter than two elements.
head :: HasCallStack => ShortByteString -> Word16 Source #
O(1) Extract the first element of a ShortByteString, which must be at least one Word16. An exception will be thrown in the case of an empty ShortByteString.
init :: HasCallStack => ShortByteString -> ShortByteString Source #
O(n) Return all the elements of a ShortByteString
except the last one.
An exception will be thrown in the case of an empty ShortByteString.
Note: copies the entire byte array
unsnoc :: ShortByteString -> Maybe (ShortByteString, Word16) Source #
null :: ShortByteString -> Bool Source #
O(1) Test whether a ShortByteString
is empty.
length :: ShortByteString -> Int Source #
O(1) The length of a ShortByteString
.
numWord16 :: ShortByteString -> Int Source #
Transforming ShortByteStrings
map :: (Word16 -> Word16) -> ShortByteString -> ShortByteString Source #
O(n) map
f xs
is the ShortByteString obtained by applying f
to each
element of xs
.
reverse :: ShortByteString -> ShortByteString Source #
O(n) reverse
xs
efficiently returns the elements of xs
in reverse order.
intercalate :: ShortByteString -> [ShortByteString] -> ShortByteString Source #
O(n) The intercalate
function takes a ShortByteString
and a list of
ShortByteString
s and concatenates the list after interspersing the first
argument between each element of the list.
Since: bytestring-0.11.3.0
Reducing ShortByteString
s (folds)
foldl :: (a -> Word16 -> a) -> a -> ShortByteString -> a Source #
foldl
, applied to a binary operator, a starting value (typically
the left-identity of the operator), and a ShortByteString, reduces the
ShortByteString using the binary operator, from left to right.
foldl' :: (a -> Word16 -> a) -> a -> ShortByteString -> a Source #
foldl1 :: HasCallStack => (Word16 -> Word16 -> Word16) -> ShortByteString -> Word16 Source #
foldl1
is a variant of foldl
that has no starting value
argument, and thus must be applied to non-empty ShortByteString
s.
An exception will be thrown in the case of an empty ShortByteString.
foldl1' :: HasCallStack => (Word16 -> Word16 -> Word16) -> ShortByteString -> Word16 Source #
foldr :: (Word16 -> a -> a) -> a -> ShortByteString -> a Source #
foldr
, applied to a binary operator, a starting value
(typically the right-identity of the operator), and a ShortByteString,
reduces the ShortByteString using the binary operator, from right to left.
foldr' :: (Word16 -> a -> a) -> a -> ShortByteString -> a Source #
foldr1 :: HasCallStack => (Word16 -> Word16 -> Word16) -> ShortByteString -> Word16 Source #
foldr1
is a variant of foldr
that has no starting value argument,
and thus must be applied to non-empty ShortByteString
s
An exception will be thrown in the case of an empty ShortByteString.
foldr1' :: HasCallStack => (Word16 -> Word16 -> Word16) -> ShortByteString -> Word16 Source #
Special folds
all :: (Word16 -> Bool) -> ShortByteString -> Bool Source #
O(n) Applied to a predicate and a ShortByteString
, all
determines
if all elements of the ShortByteString
satisfy the predicate.
any :: (Word16 -> Bool) -> ShortByteString -> Bool Source #
O(n) Applied to a predicate and a ByteString, any
determines if
any element of the ByteString
satisfies the predicate.
concat :: [ShortByteString] -> ShortByteString Source #
Generating and unfolding ByteStrings
replicate :: Int -> Word16 -> ShortByteString Source #
O(n) replicate
n x
is a ByteString 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 (Word16, a)) -> a -> ShortByteString Source #
O(n), where n is the length of the result. The unfoldr
function is analogous to the List 'unfoldr'. unfoldr
builds a
ShortByteString from a seed value. The function takes the element and
returns Nothing
if it is done producing the ShortByteString 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 [Word16]
and run the generator until it returns Nothing
, otherwise recurse infinitely,
then finally create a ShortByteString
.
Examples:
unfoldr (\x -> if x <= 5 then Just (x, x + 1) else Nothing) 0 == pack [0, 1, 2, 3, 4, 5]
O(n) Like unfoldr
, unfoldrN
builds a ShortByteString 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
:: Int | number of Word16 |
-> ShortByteString | |
-> ShortByteString |
:: Int | number of |
-> ShortByteString | |
-> ShortByteString |
takeWhileEnd :: (Word16 -> Bool) -> ShortByteString -> ShortByteString Source #
Returns the longest (possibly empty) suffix of elements satisfying the predicate.
is equivalent to takeWhileEnd
p
.reverse
. takeWhile
p . reverse
takeWhile :: (Word16 -> Bool) -> ShortByteString -> ShortByteString Source #
Similar to takeWhile
,
returns the longest (possibly empty) prefix of elements
satisfying the predicate.
:: Int | number of |
-> ShortByteString | |
-> ShortByteString |
:: Int | number of |
-> ShortByteString | |
-> ShortByteString |
dropWhile :: (Word16 -> Bool) -> ShortByteString -> ShortByteString Source #
Similar to dropWhile
,
drops the longest (possibly empty) prefix of elements
satisfying the predicate and returns the remainder.
Note: copies the entire byte array
dropWhileEnd :: (Word16 -> Bool) -> ShortByteString -> ShortByteString 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: filepath-0.10.12.0
breakEnd :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString) 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))
break :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString) Source #
span :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString) Source #
spanEnd :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString) 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) ps == let (x, y) = span (not . isSpace) (reverse ps) in (reverse y, reverse x)
:: Int | number of Word16 |
-> ShortByteString | |
-> (ShortByteString, ShortByteString) |
split :: Word16 -> ShortByteString -> [ShortByteString] Source #
O(n) Break a ShortByteString
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 . (==)
Note: copies the substrings
splitWith :: (Word16 -> Bool) -> ShortByteString -> [ShortByteString] Source #
O(n) Splits a ShortByteString
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 :: ShortByteString -> ShortByteString -> Maybe ShortByteString Source #
O(n) The stripSuffix
function takes two ShortByteStrings and returns Just
the remainder of the second iff the first is its suffix, and otherwise
Nothing
.
Since: bytestring-0.11.3.0
stripPrefix :: ShortByteString -> ShortByteString -> Maybe ShortByteString Source #
O(n) The stripPrefix
function takes two ShortByteStrings and returns Just
the remainder of the second iff the first is its prefix, and otherwise
Nothing
.
Since: bytestring-0.11.3.0
Predicates
isInfixOf :: ShortByteString -> ShortByteString -> Bool Source #
Check whether one string is a substring of another.
isPrefixOf :: ShortByteString -> ShortByteString -> Bool Source #
O(n) The isPrefixOf
function takes two ShortByteStrings and returns True
Since: bytestring-0.11.3.0
isSuffixOf :: ShortByteString -> ShortByteString -> Bool Source #
O(n) The isSuffixOf
function takes two ShortByteStrings and returns True
iff the first is a suffix of the second.
The following holds:
isSuffixOf x y == reverse x `isPrefixOf` reverse y
Since: bytestring-0.11.3.0
Search for arbitrary substrings
:: ShortByteString | String to search for |
-> ShortByteString | String to search in |
-> (ShortByteString, ShortByteString) | Head and tail of string broken at substring |
Searching ShortByteStrings
Searching by equality
elem :: Word16 -> ShortByteString -> Bool Source #
O(n) elem
is the ShortByteString
membership predicate.
Searching with a predicate
filter :: (Word16 -> Bool) -> ShortByteString -> ShortByteString Source #
O(n) filter
, applied to a predicate and a ByteString,
returns a ByteString containing those characters that satisfy the
predicate.
partition :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString) Source #
O(n) The partition
function takes a predicate a ByteString and returns
the pair of ByteStrings with elements which do and do not satisfy the
predicate, respectively; i.e.,
partition p bs == (filter p xs, filter (not . p) xs)
Indexing ShortByteStrings
:: HasCallStack | |
=> ShortByteString | |
-> Int | number of |
-> Word16 |
O(1) ShortByteString
index (subscript) operator, starting from 0.
:: ShortByteString | |
-> Int | number of |
-> Maybe Word16 |
O(1) ShortByteString
index, starting from 0, that returns Just
if:
0 <= n < length bs
Since: filepath-0.11.0.0
:: ShortByteString | |
-> Int | number of |
-> Maybe Word16 |
O(1) ShortByteString
index, starting from 0, that returns Just
if:
0 <= n < length bs
Since: filepath-0.11.0.0
:: Word16 | |
-> ShortByteString | |
-> Maybe Int | number of |
O(n) The elemIndex
function returns the index of the first
element in the given ShortByteString
which is equal to the query
element, or Nothing
if there is no such element.
elemIndices :: Word16 -> ShortByteString -> [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 :: Word16 -> ShortByteString -> Int Source #
count returns the number of times its argument appears in the ShortByteString
findIndex :: (Word16 -> Bool) -> ShortByteString -> Maybe Int Source #
O(n) The findIndex
function takes a predicate and a ShortByteString
and
returns the index of the first element in the ByteString
satisfying the predicate.
findIndices :: (Word16 -> Bool) -> ShortByteString -> [Int] Source #
O(n) The findIndices
function extends findIndex
, by returning the
indices of all elements satisfying the predicate, in ascending order.
Encoding validation
Low level conversions
Packing CString
s and pointers
packCWString :: Ptr Word16 -> IO ShortByteString Source #
O(n). Construct a new ShortByteString
from a CWString
. The
resulting ShortByteString
is an immutable copy of the original
CWString
, and is managed on the Haskell heap. The original
CWString
must be null terminated.
Since: filepath-0.10.10.0
packCWStringLen :: (Ptr Word16, Int) -> IO ShortByteString Source #
O(n). Construct a new ShortByteString
from a CWStringLen
. The
resulting ShortByteString
is an immutable copy of the original CWStringLen
.
The ShortByteString
is a normal Haskell value and will be managed on the
Haskell heap.
Since: filepath-0.10.10.0
newCWString :: ShortByteString -> IO (Ptr Word16) Source #
O(n) construction. Use a ShortByteString
with a function requiring a CWStringLen
.
As for useAsCWString
this function makes a copy of the original ShortByteString
.
It must not be stored or used after the subcomputation finishes.
Since: filepath-0.10.10.0
Using ShortByteStrings as CString
s
useAsCWString :: ShortByteString -> (Ptr Word16 -> IO a) -> IO a Source #
O(n) construction. Use a ShortByteString
with a function requiring a
null-terminated CWString
. The CWString
is a copy and will be freed
automatically; it must not be stored or used after the
subcomputation finishes.
Since: filepath-0.10.10.0
useAsCWStringLen :: ShortByteString -> ((Ptr Word16, Int) -> IO a) -> IO a Source #
O(n) construction. Use a ShortByteString
with a function requiring a CWStringLen
.
As for useAsCWString
this function makes a copy of the original ShortByteString
.
It must not be stored or used after the subcomputation finishes.
Since: filepath-0.10.10.0