| Copyright | (c) Dong Han 2017-2018 |
|---|---|
| License | BSD |
| Maintainer | winterland1989@gmail.com |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Z.Data.CBytes
Contents
Description
This module provide CBytes with some useful instances / functions, A CBytes is a
wrapper for immutable null-terminated string.
The main design target 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.
We neither guarantee to store length info, nor support O(1) slice for CBytes:
This will defeat the purpose of null-terminated string which is to save memory,
We do save the length if it's created on GHC heap though. If you need advance editing,
convert a CBytes to Bytes with toBytes and use vector combinators.
Use fromBytes to convert it back.
It can be used with OverloadedString, literal encoding is UTF-8 with some modifications:
NUL char is encoded to 'C0 80', and '\xD800' ~ '\xDFFF' is encoded as a three bytes
normal utf-8 codepoint. This is also how ghc compile string literal into binaries,
thus we can use rewrite-rules to construct CBytes value in O(1) without wasting runtime heap.
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 everywhere, and we use UTF-8 assumption in
various places, such as displaying CBytes and literals encoding above.
Synopsis
- data CBytes
- create :: HasCallStack => Int -> (CString -> IO Int) -> IO CBytes
- 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
- fromCString :: CString -> IO CBytes
- fromCString' :: HasCallStack => CString -> IO (Maybe CBytes)
- fromCStringN :: CString -> Int -> IO CBytes
- withCBytes :: CBytes -> (CString -> IO a) -> IO a
- allocCBytes :: HasCallStack => Int -> (CString -> IO a) -> IO (CBytes, a)
- w2c :: Word8 -> Char
- c2w :: Char -> Word8
- data NullPointerException = NullPointerException CallStack
- type CString = Ptr CChar
Documentation
A efficient wrapper for immutable null-terminated string which can be automatically freed by ghc garbage collector.
Instances
| Eq CBytes Source # | |
| Ord CBytes Source # | |
| Read CBytes Source # | |
| Show CBytes Source # | |
| IsString CBytes Source # | |
Defined in Z.Data.CBytes Methods fromString :: String -> CBytes # | |
| Semigroup CBytes Source # | |
| Monoid CBytes Source # | |
| NFData CBytes Source # | |
Defined in Z.Data.CBytes | |
| Hashable CBytes Source # | |
Defined in Z.Data.CBytes | |
Arguments
| :: HasCallStack | |
| => Int | capacity n, including the |
| -> (CString -> IO Int) | initialize function write the pointer, return the length (<= n-1) |
| -> IO CBytes |
Create a CBytes with IO action.
User only have to do content initialization and return the content length,
create takes the responsibility to add the NUL ternimator. If the
initialize function write NUL terminator(most FFI functions for example),
you should use allocCBytes.
If (<=0) capacity is provided, a nullPtr is passed to initialize function and
empty will be returned. other than that, if length returned is larger than (capacity-1),
a NULLTerminatorNotFound will be thrown.
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.
toBytes :: CBytes -> Bytes Source #
O(1), (O(n) in case of literal), convert to Bytes, which can be
processed by vector combinators.
NOTE: the NUL ternimator is not included.
fromBytes :: Bytes -> CBytes Source #
O(n), convert from Bytes, allocate pinned memory and
add the NUL ternimator
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, allocate pinned memory and
add the NUL ternimator
fromCString' :: HasCallStack => CString -> IO (Maybe CBytes) Source #
Same with fromCString, but throw NullPointerException when meet a null pointer.
fromCStringN :: CString -> Int -> IO CBytes Source #
Same with fromCString, but only take N bytes (and append a null byte as terminator).
exception
data NullPointerException Source #
Constructors
| NullPointerException CallStack |
Instances
| Show NullPointerException Source # | |
Defined in Z.Data.CBytes Methods showsPrec :: Int -> NullPointerException -> ShowS # show :: NullPointerException -> String # showList :: [NullPointerException] -> ShowS # | |
| Exception NullPointerException Source # | |
Defined in Z.Data.CBytes Methods toException :: NullPointerException -> SomeException # fromException :: SomeException -> Maybe NullPointerException # | |