base-4.4.0.0: Basic libraries

Portabilityportable
Stabilityprovisional
Maintainer[email protected]

Foreign.C.String

Contents

Description

Utilities for primitive marshalling of C strings.

The marshalling converts each Haskell character, representing a Unicode code point, to one or more bytes in a manner that, by default, is determined by the current locale. As a consequence, no guarantees can be made about the relative length of a Haskell string and its corresponding C string, and therefore all the marshalling routines include memory allocation. The translation between Unicode and the encoding of the current locale may be lossy.

Synopsis

C strings

type CString = Ptr CCharSource

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

type CStringLen = (Ptr CChar, Int)Source

A string with explicit length information in bytes instead of a terminating NUL (allowing NUL characters in the middle of the string).

Using a locale-dependent encoding

These functions are different from their CAString counterparts in that they will use an encoding determined by the current locale, rather than always assuming ASCII.

peekCString :: CString -> IO StringSource

Marshal a NUL terminated C string into a Haskell string.

peekCStringLen :: CStringLen -> IO StringSource

Marshal a C string with explicit length into a Haskell string.

newCString :: String -> IO CStringSource

Marshal a Haskell string into a NUL terminated C string.

  • the Haskell string may not contain any NUL characters
  • new storage is allocated for the C string and must be explicitly freed using Foreign.Marshal.Alloc.free or Foreign.Marshal.Alloc.finalizerFree.

newCStringLen :: String -> IO CStringLenSource

Marshal a Haskell string into a C string (ie, character array) with explicit length information.

  • new storage is allocated for the C string and must be explicitly freed using Foreign.Marshal.Alloc.free or Foreign.Marshal.Alloc.finalizerFree.

withCString :: String -> (CString -> IO a) -> IO aSource

Marshal a Haskell string into a NUL terminated C string using temporary storage.

  • the Haskell string may not contain any NUL characters
  • the memory is freed when the subcomputation terminates (either normally or via an exception), so the pointer to the temporary storage must not be used after this.

withCStringLen :: String -> (CStringLen -> IO a) -> IO aSource

Marshal a Haskell string into a C string (ie, character array) in temporary storage, with explicit length information.

  • the memory is freed when the subcomputation terminates (either normally or via an exception), so the pointer to the temporary storage must not be used after this.

Using 8-bit characters

These variants of the above functions are for use with C libraries that are ignorant of Unicode. These functions should be used with care, as a loss of information can occur.

castCharToCChar :: Char -> CCharSource

Convert a Haskell character to a C character. This function is only safe on the first 256 characters.

castCCharToChar :: CChar -> CharSource

Convert a C byte, representing a Latin-1 character, to the corresponding Haskell character.

castCharToCUChar :: Char -> CUCharSource

Convert a Haskell character to a C unsigned char. This function is only safe on the first 256 characters.

castCUCharToChar :: CUChar -> CharSource

Convert a C unsigned char, representing a Latin-1 character, to the corresponding Haskell character.

castCharToCSChar :: Char -> CSCharSource

Convert a Haskell character to a C signed char. This function is only safe on the first 256 characters.

castCSCharToChar :: CSChar -> CharSource

Convert a C signed char, representing a Latin-1 character, to the corresponding Haskell character.

peekCAString :: CString -> IO StringSource

Marshal a NUL terminated C string into a Haskell string.

peekCAStringLen :: CStringLen -> IO StringSource

Marshal a C string with explicit length into a Haskell string.

newCAString :: String -> IO CStringSource

Marshal a Haskell string into a NUL terminated C string.

  • the Haskell string may not contain any NUL characters
  • new storage is allocated for the C string and must be explicitly freed using Foreign.Marshal.Alloc.free or Foreign.Marshal.Alloc.finalizerFree.

newCAStringLen :: String -> IO CStringLenSource

Marshal a Haskell string into a C string (ie, character array) with explicit length information.

  • new storage is allocated for the C string and must be explicitly freed using Foreign.Marshal.Alloc.free or Foreign.Marshal.Alloc.finalizerFree.

withCAString :: String -> (CString -> IO a) -> IO aSource

Marshal a Haskell string into a NUL terminated C string using temporary storage.

  • the Haskell string may not contain any NUL characters
  • the memory is freed when the subcomputation terminates (either normally or via an exception), so the pointer to the temporary storage must not be used after this.

withCAStringLen :: String -> (CStringLen -> IO a) -> IO aSource

Marshal a Haskell string into a C string (ie, character array) in temporary storage, with explicit length information.

  • the memory is freed when the subcomputation terminates (either normally or via an exception), so the pointer to the temporary storage must not be used after this.

C wide strings

These variants of the above functions are for use with C libraries that encode Unicode using the C wchar_t type in a system-dependent way. The only encodings supported are

  • UTF-32 (the C compiler defines __STDC_ISO_10646__), or
  • UTF-16 (as used on Windows systems).

type CWString = Ptr CWcharSource

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

type CWStringLen = (Ptr CWchar, Int)Source

A wide character string with explicit length information in CWchars instead of a terminating NUL (allowing NUL characters in the middle of the string).

peekCWString :: CWString -> IO StringSource

Marshal a NUL terminated C wide string into a Haskell string.

peekCWStringLen :: CWStringLen -> IO StringSource

Marshal a C wide string with explicit length into a Haskell string.

newCWString :: String -> IO CWStringSource

Marshal a Haskell string into a NUL terminated C wide string.

  • the Haskell string may not contain any NUL characters
  • new storage is allocated for the C wide string and must be explicitly freed using Foreign.Marshal.Alloc.free or Foreign.Marshal.Alloc.finalizerFree.

newCWStringLen :: String -> IO CWStringLenSource

Marshal a Haskell string into a C wide string (ie, wide character array) with explicit length information.

  • new storage is allocated for the C wide string and must be explicitly freed using Foreign.Marshal.Alloc.free or Foreign.Marshal.Alloc.finalizerFree.

withCWString :: String -> (CWString -> IO a) -> IO aSource

Marshal a Haskell string into a NUL terminated C wide string using temporary storage.

  • the Haskell string may not contain any NUL characters
  • the memory is freed when the subcomputation terminates (either normally or via an exception), so the pointer to the temporary storage must not be used after this.

withCWStringLen :: String -> (CWStringLen -> IO a) -> IO aSource

Marshal a Haskell string into a NUL terminated C wide string using temporary storage.

  • the Haskell string may not contain any NUL characters
  • the memory is freed when the subcomputation terminates (either normally or via an exception), so the pointer to the temporary storage must not be used after this.