Copyright | (c) Dong Han 2017-2018 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
- - This module provide
CBytes
with some useful instances / tools for retrieving, storing or processing - - short byte sequences, such as file path, environment variables, etc.
Synopsis
- data CBytes where
- toPrimArray :: CBytes -> PrimArray Word8
- pack :: String -> CBytes
- unpack :: CBytes -> String
- null :: CBytes -> Bool
- length :: CBytes -> Int
- empty :: CBytes
- append :: CBytes -> CBytes -> CBytes
- concat :: [CBytes] -> CBytes
- intercalate :: CBytes -> [CBytes] -> CBytes
- intercalateElem :: Word8 -> [CBytes] -> CBytes
- toBytes :: CBytes -> Bytes
- fromBytes :: Bytes -> CBytes
- toText :: CBytes -> Text
- toTextMaybe :: CBytes -> Maybe Text
- fromText :: Text -> CBytes
- toBuilder :: CBytes -> Builder ()
- buildCBytes :: Builder a -> CBytes
- fromCString :: CString -> IO CBytes
- fromCStringN :: CString -> Int -> IO CBytes
- withCBytesUnsafe :: CBytes -> (BA# Word8 -> IO a) -> IO a
- withCBytes :: CBytes -> (Ptr Word8 -> IO a) -> IO a
- allocCBytesUnsafe :: HasCallStack => Int -> (MBA# Word8 -> IO a) -> IO (CBytes, a)
- allocCBytes :: HasCallStack => Int -> (CString -> IO a) -> IO (CBytes, a)
- type CString = Ptr CChar
- c2w :: Char -> Word8
- w2c :: Word8 -> Char
Documentation
A efficient wrapper for short immutable null-terminated byte sequences which can be automatically freed by ghc garbage collector.
The main use case of this type is to ease the bridging of C FFI APIs, since most of the unix APIs use null-terminated string. On windows you're encouraged to use a compatibility layer like 'WideCharToMultiByte/MultiByteToWideChar' and keep the same interface, e.g. libuv do this when deal with file paths.
CBytes
don't support O(1) slicing, it's not suitable to use it to store large byte
chunk, If you need advance editing, convert CBytes
to / from PrimArray
with CB
,
or Bytes
with 'toBytes\/fromBytes' if you need O(1) slicing, then use vector combinators.
When textual represatation is needed(conver to String
, Text
, Show
instance, etc.),
we assume CBytes
using UTF-8 encodings, CBytes
can be used with OverloadedString
,
literal encoding is UTF-8 with some modifications: NUL
is encoded to 'C0 80',
and '\xD800' ~ '\xDFFF' is encoded as a three bytes normal utf-8 codepoint.
Note most of the unix API is not unicode awared though, you may find a scandir
call
return a filename which is not proper encoded in any unicode encoding at all.
But still, UTF-8 is recommanded to be used when text represatation is needed.
--
pattern CB :: PrimArray Word8 -> CBytes | Use this pattern to match or construct |
Instances
toPrimArray :: CBytes -> PrimArray Word8 Source #
Convert to PrimArray
,
there's an invariance that this array never contains NUL
unpack :: CBytes -> String Source #
O(n) Convert cbytes to a char list using UTF8 encoding assumption.
This function is much tolerant than toText
, it simply decoding codepoints using UTF8 decodeChar
without checking errors such as overlong or invalid range.
Unpacking is done lazily. i.e. we will retain reference to the array until all element are consumed.
This function is a good producer in the sense of build/foldr fusion.
intercalate :: CBytes -> [CBytes] -> CBytes Source #
O(n) The intercalate
function takes a CBytes
and a list of
CBytes
s and concatenates the list after interspersing the first
argument between each element of the list.
Note: intercalate
will force the entire CBytes
list.
intercalateElem :: Word8 -> [CBytes] -> CBytes Source #
O(n) An efficient way to join CByte
s with a byte.
Intercalate bytes list with NUL
will effectively leave the first bytes in the list.
toBytes :: CBytes -> Bytes Source #
O(1), convert to Bytes
, which can be processed by vector combinators.
fromBytes :: Bytes -> CBytes Source #
O(n), convert from Bytes
Result will be trimmed down to first byte before NUL
byte if there's any.
toText :: CBytes -> Text Source #
O(n), convert to Text
using UTF8 encoding assumption.
Throw InvalidUTF8Exception
in case of invalid codepoint.
fromText :: Text -> CBytes Source #
O(n), convert from Text
,
Result will be trimmed down to first byte before NUL
byte if there's any.
toBuilder :: CBytes -> Builder () Source #
Write CBytes
's byte sequence to buffer.
This function is different from ShowT
instance in that it directly write byte sequence without
checking if it's UTF8 encoded.
buildCBytes :: Builder a -> CBytes Source #
Build a CBytes
with builder, result will be trimmed down to first byte before NUL
byte if there's any.
fromCStringN :: CString -> Int -> IO CBytes Source #
Same with fromCString
, but only take at most N bytes.
Result will be trimmed down to first byte before NUL
byte if there's any.
withCBytesUnsafe :: CBytes -> (BA# Word8 -> IO a) -> IO a Source #
Pass CBytes
to foreign function as a const char*
.
USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY.
:: HasCallStack | |
=> Int | capacity n(include the |
-> (MBA# Word8 -> IO a) | initialization function, |
-> IO (CBytes, a) |
Create a CBytes
with IO action.
If (<=0) capacity is provided, a pointer pointing to NUL
is passed to initialize function
and empty
will be returned. This behavior is different from allocCBytes
, which may cause
trouble for some FFI functions.
USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY.