regional-pointers-0.6: Regional memory pointers

MaintainerBas van Dijk <v.dijk.bas@gmail.com>

Foreign.C.String.Region

Contents

Description

Lifts functions and types from Foreign.C.String to regional pointers.

Synopsis

Regional C Strings

type RegionalCString pointer r = pointer CChar rSource

Handy type synonym for a regional pointer to an array of C characters terminated by a NUL.

This should provide a safer replacement for Foreign.C.String.CString.

type RegionalCStringLen pointer r = (RegionalCString pointer r, Int)Source

Handy type synonym for a regional pointer to an array of C characters which is paired with the length of the array instead of terminated by a NUL. (Thus allowing NUL characters in the middle of the string)

This should provide a safer replacement for Foreign.C.String.CStringLen.

Using a locale-dependent encoding

peekCString :: (AllocatedPointer pointer, AncestorRegion pr cr, MonadIO cr) => RegionalCString pointer pr -> cr StringSource

Marshal a NUL terminated C string into a Haskell string.

Wraps: Foreign.C.String.peekCString

peekCStringLen :: (AllocatedPointer pointer, AncestorRegion pr cr, MonadIO cr) => RegionalCStringLen pointer pr -> cr StringSource

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

Wraps: Foreign.C.String.peekCStringLen.

newCString :: MonadControlIO pr => String -> RegionT s pr (RegionalCString RegionalPtr (RegionT s pr))Source

Marshal a Haskell string into a NUL terminated C string.

The Haskell string may not contain any NUL characters

Wraps: Foreign.C.String.newCString.

newCStringLen :: MonadControlIO pr => String -> RegionT s pr (RegionalCStringLen RegionalPtr (RegionT s pr))Source

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

Wraps: Foreign.C.String.newCStringLen.

withCString :: MonadControlIO pr => String -> (forall sl. RegionalCString LocalPtr (LocalRegion sl s) -> RegionT (Local s) pr α) -> RegionT s pr αSource

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

Wraps: Foreign.C.String.withCString.

withCStringLen :: MonadControlIO pr => String -> (forall sl. RegionalCStringLen LocalPtr (LocalRegion sl s) -> RegionT (Local s) pr α) -> RegionT s pr αSource

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

Wraps: Foreign.C.String.withCStringLen.

charIsRepresentable :: MonadIO m => Char -> m BoolSource

Generalizes Foreign.C.String.charIsRepresentable to any MonadIO.

Using 8-bit characters

castCharToCChar :: Char -> CChar

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

castCCharToChar :: CChar -> Char

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

castCharToCUChar :: Char -> CUChar

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

castCUCharToChar :: CUChar -> Char

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

castCharToCSChar :: Char -> CSChar

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

castCSCharToChar :: CSChar -> Char

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

peekCAString :: (AllocatedPointer pointer, AncestorRegion pr cr, MonadIO cr) => RegionalCString pointer pr -> cr StringSource

Marshal a NUL terminated C string into a Haskell string.

Wraps: Foreign.C.String.peekCAString.

peekCAStringLen :: (AllocatedPointer pointer, AncestorRegion pr cr, MonadIO cr) => RegionalCStringLen pointer pr -> cr StringSource

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

Wraps: Foreign.C.String.peekCAStringLen.

newCAString :: MonadControlIO pr => String -> RegionT s pr (RegionalCString RegionalPtr (RegionT s pr))Source

Marshal a Haskell string into a NUL terminated C string.

The Haskell string may not contain any NUL characters

Wraps: Foreign.C.String.newCAString.

newCAStringLen :: MonadControlIO pr => String -> RegionT s pr (RegionalCStringLen RegionalPtr (RegionT s pr))Source

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

Wraps: Foreign.C.String.newCAStringLen.

withCAString :: MonadControlIO pr => String -> (forall sl. RegionalCString LocalPtr (LocalRegion sl s) -> RegionT (Local s) pr α) -> RegionT s pr αSource

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

Wraps: Foreign.C.String.withCAString.

withCAStringLen :: MonadControlIO pr => String -> (forall sl. RegionalCStringLen LocalPtr (LocalRegion sl s) -> RegionT (Local s) pr α) -> RegionT s pr αSource

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

Wraps: Foreign.C.String.withCAStringLen.

C wide strings

type RegionalCWString pointer r = pointer CWchar rSource

Handy type synonym for a regional pointer to an array of C wide characters terminated by a NUL.

This should provide a safer replacement for Foreign.C.String.CWString.

type RegionalCWStringLen pointer r = (RegionalCWString pointer r, Int)Source

Handy type synonym for a regional pointer to an array of C wide characters which is paired with the length of the array instead of terminated by a NUL. (Thus allowing NUL characters in the middle of the string)

This should provide a safer replacement for Foreign.C.String.CWStringLen.

peekCWString :: (AllocatedPointer pointer, AncestorRegion pr cr, MonadIO cr) => RegionalCWString pointer pr -> cr StringSource

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

Wraps: Foreign.C.String.peekCWString.

peekCWStringLen :: (AllocatedPointer pointer, AncestorRegion pr cr, MonadIO cr) => RegionalCWStringLen pointer pr -> cr StringSource

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

Wraps: Foreign.C.String.peekCWStringLen.

newCWString :: MonadControlIO pr => String -> RegionT s pr (RegionalCWString RegionalPtr (RegionT s pr))Source

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

The Haskell string may not contain any NUL characters.

Wraps: Foreign.C.String.newCWString.

newCWStringLen :: MonadControlIO pr => String -> RegionT s pr (RegionalCWStringLen RegionalPtr (RegionT s pr))Source

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

Wraps: Foreign.C.String.newCWStringLen.

withCWString :: MonadControlIO pr => String -> (forall sl. RegionalCWString LocalPtr (LocalRegion sl s) -> RegionT (Local s) pr α) -> RegionT s pr αSource

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

Wraps: Foreign.C.String.withCWString.

withCWStringLen :: MonadControlIO pr => String -> (forall sl. RegionalCWStringLen LocalPtr (LocalRegion sl s) -> RegionT (Local s) pr α) -> RegionT s pr αSource

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

Wraps: Foreign.C.String.withCWStringLen.