Z-Data-0.2.0.0: Array, vector and text
Copyright(c) Dong Han 2017-2018
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.Data.CBytes

Description

This module provides CBytes with some useful instances / tools for retrieving, storing or processing short byte sequences, such as file path, environment variables, etc.

Synopsis

The CBytes type

data CBytes where Source #

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 Bytes with CB pattern or toBytes / fromBytes, then use vector combinators.

When textual represatation is needed e.g. converting 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.

Bundled Patterns

pattern CB :: Bytes -> CBytes

Use this pattern to match or construct CBytes, result will be trimmed down to first \NUL byte if there's any.

Instances

Instances details
Eq CBytes Source # 
Instance details

Defined in Z.Data.CBytes

Methods

(==) :: CBytes -> CBytes -> Bool #

(/=) :: CBytes -> CBytes -> Bool #

Ord CBytes Source # 
Instance details

Defined in Z.Data.CBytes

Read CBytes Source # 
Instance details

Defined in Z.Data.CBytes

Show CBytes Source # 
Instance details

Defined in Z.Data.CBytes

IsString CBytes Source # 
Instance details

Defined in Z.Data.CBytes

Methods

fromString :: String -> CBytes #

Semigroup CBytes Source # 
Instance details

Defined in Z.Data.CBytes

Monoid CBytes Source # 
Instance details

Defined in Z.Data.CBytes

Arbitrary CBytes Source # 
Instance details

Defined in Z.Data.CBytes

CoArbitrary CBytes Source # 
Instance details

Defined in Z.Data.CBytes

Methods

coarbitrary :: CBytes -> Gen b -> Gen b #

NFData CBytes Source # 
Instance details

Defined in Z.Data.CBytes

Methods

rnf :: CBytes -> () #

Hashable CBytes Source # 
Instance details

Defined in Z.Data.CBytes

Methods

hashWithSalt :: Int -> CBytes -> Int #

hash :: CBytes -> Int #

Unaligned CBytes Source #

This instance peek bytes until \NUL(or input chunk ends), poke bytes with an extra \NUL terminator.

Instance details

Defined in Z.Data.CBytes

ShowT CBytes Source #

This instance provide UTF8 guarantee, illegal codepoints will be written as replacementChars.

Escaping rule is same with String.

Instance details

Defined in Z.Data.CBytes

FromValue CBytes Source #

JSON instances check if CBytes is proper UTF8 encoded, if it is, decode/encode it as Text, otherwise as Bytes.

> encodeText ("hello" :: CBytes)
""hello""
> encodeText ("hello\NUL" :: CBytes)     -- \NUL is encoded as C0 80
"[104,101,108,108,111,192,128]"
Instance details

Defined in Z.Data.CBytes

EncodeJSON CBytes Source # 
Instance details

Defined in Z.Data.CBytes

Methods

encodeJSON :: CBytes -> Builder () Source #

ToValue CBytes Source # 
Instance details

Defined in Z.Data.CBytes

Methods

toValue :: CBytes -> Value Source #

rawPrimArray :: CBytes -> PrimArray Word8 Source #

Convert to a \NUL terminated PrimArray,

There's an invariance that this array never contains extra \NUL except terminator.

fromPrimArray :: PrimArray Word8 -> CBytes Source #

Constuctor a CBytes from arbitrary array, result will be trimmed down to first \NUL byte if there's any.

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 \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.

toTextMaybe :: CBytes -> Maybe Text Source #

O(n), convert to Text using UTF8 encoding assumption.

Return Nothing in case of invalid codepoint.

fromText :: Text -> CBytes Source #

O(n), convert from Text,

Result will be trimmed down to first \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 \NUL byte if there's any.

pack :: String -> CBytes Source #

Pack a String into CBytes.

\NUL is encoded as two bytes C0 80 , \xD800 ~ \xDFFF is encoded as a three bytes normal UTF-8 codepoint.

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.

null :: CBytes -> Bool Source #

Return True if CBytes is empty.

length :: CBytes -> Int Source #

O(1), Return the BTYE length of CBytes.

append :: CBytes -> CBytes -> CBytes Source #

Concatenate two CBytes.

concat :: [CBytes] -> CBytes Source #

O(n) Concatenate a list of CBytes.

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.

fromCString :: CString -> IO CBytes Source #

Copy a CString type into a CBytes, return empty if the pointer is NULL.

After copying you're free to free the CString 's memory.

fromCStringN :: CString -> Int -> IO CBytes Source #

Same with fromCString, but only take at most N bytes.

Result will be trimmed down to first \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.

withCBytes :: CBytes -> (Ptr Word8 -> IO a) -> IO a Source #

Pass CBytes to foreign function as a const char*.

Don't pass a forever loop to this function, see #14346.

allocCBytesUnsafe Source #

Arguments

:: HasCallStack 
=> Int

capacity n(including the \NUL terminator)

-> (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.

allocCBytes Source #

Arguments

:: HasCallStack 
=> Int

capacity n(including the \NUL terminator)

-> (CString -> IO a)

initialization function,

-> IO (CBytes, a) 

Create a CBytes with IO action.

If (<=0) capacity is provided, a nullPtr is passed to initialize function and empty will be returned. Other than that, User have to make sure a \NUL ternimated string will be written.

withCBytesListUnsafe :: [CBytes] -> (BAArray# Word8 -> Int -> IO a) -> IO a Source #

Pass CBytes list to foreign function as a StgArrBytes**.

Enable UnliftedFFITypes extension in your haskell code, use StgArrBytes**(>=8.10) or StgMutArrPtrs*(<8.10) pointer type and HsInt to marshall BAArray# and Int arguments on C side, check the example with BAArray#.

USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY.

withCBytesList :: [CBytes] -> (Ptr (Ptr Word8) -> Int -> IO a) -> IO a Source #

Pass CBytes list to foreign function as a const char**.

Check Z.Foreign module for more detail on how to marshall params in C side.

re-export

type CString = Ptr CChar #

A C string is a reference to an array of C characters terminated by NUL.

c2w :: Char -> Word8 Source #

Unsafe conversion between Char and Word8. This is a no-op and silently truncates to 8 bits Chars > \255. It is provided as convenience for PrimVector construction.

w2c :: Word8 -> Char Source #

Conversion between Word8 and Char. Should compile to a no-op.