text-2.1.1: An efficient packed Unicode text type.
Copyright(c) 2009 2010 Bryan O'Sullivan
LicenseBSD-style
Maintainerbos@serpentine.com
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Text.Foreign

Description

Support for using Text data with native code via the Haskell foreign function interface.

Synopsis

Interoperability with native code

The Text type is implemented using arrays that are not guaranteed to have a fixed address in the Haskell heap. All communication with native code must thus occur by copying data back and forth.

The Text type's internal representation is UTF-8. To interoperate with native libraries that use different internal representations, such as UTF-16 or UTF-32, consider using the functions in the Encoding module.

data I8 Source #

A type representing a number of UTF-8 code units.

Since: 2.0

Instances

Instances details
Bounded I8 Source # 
Instance details

Defined in Data.Text.Foreign

Methods

minBound :: I8 #

maxBound :: I8 #

Enum I8 Source # 
Instance details

Defined in Data.Text.Foreign

Methods

succ :: I8 -> I8 #

pred :: I8 -> I8 #

toEnum :: Int -> I8 #

fromEnum :: I8 -> Int #

enumFrom :: I8 -> [I8] #

enumFromThen :: I8 -> I8 -> [I8] #

enumFromTo :: I8 -> I8 -> [I8] #

enumFromThenTo :: I8 -> I8 -> I8 -> [I8] #

Num I8 Source # 
Instance details

Defined in Data.Text.Foreign

Methods

(+) :: I8 -> I8 -> I8 #

(-) :: I8 -> I8 -> I8 #

(*) :: I8 -> I8 -> I8 #

negate :: I8 -> I8 #

abs :: I8 -> I8 #

signum :: I8 -> I8 #

fromInteger :: Integer -> I8 #

Read I8 Source # 
Instance details

Defined in Data.Text.Foreign

Integral I8 Source # 
Instance details

Defined in Data.Text.Foreign

Methods

quot :: I8 -> I8 -> I8 #

rem :: I8 -> I8 -> I8 #

div :: I8 -> I8 -> I8 #

mod :: I8 -> I8 -> I8 #

quotRem :: I8 -> I8 -> (I8, I8) #

divMod :: I8 -> I8 -> (I8, I8) #

toInteger :: I8 -> Integer #

Real I8 Source # 
Instance details

Defined in Data.Text.Foreign

Methods

toRational :: I8 -> Rational #

Show I8 Source # 
Instance details

Defined in Data.Text.Foreign

Methods

showsPrec :: Int -> I8 -> ShowS #

show :: I8 -> String #

showList :: [I8] -> ShowS #

Eq I8 Source # 
Instance details

Defined in Data.Text.Foreign

Methods

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

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

Ord I8 Source # 
Instance details

Defined in Data.Text.Foreign

Methods

compare :: I8 -> I8 -> Ordering #

(<) :: I8 -> I8 -> Bool #

(<=) :: I8 -> I8 -> Bool #

(>) :: I8 -> I8 -> Bool #

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

max :: I8 -> I8 -> I8 #

min :: I8 -> I8 -> I8 #

Safe conversion functions

fromPtr Source #

Arguments

:: Ptr Word8

source array

-> I8

length of source array (in Word8 units)

-> IO Text 

O(n) Create a new Text from a Ptr Word8 by copying the contents of the array.

fromPtr0 Source #

Arguments

:: Ptr Word8

source array

-> IO Text 

O(n) Create a new Text from a Ptr Word8 by copying the contents of the NUL-terminated array.

Since: 2.0.1

useAsPtr :: Text -> (Ptr Word8 -> I8 -> IO a) -> IO a Source #

O(n) Perform an action on a temporary, mutable copy of a Text. The copy is freed as soon as the action returns.

asForeignPtr :: Text -> IO (ForeignPtr Word8, I8) Source #

O(n) Make a mutable copy of a Text.

Encoding as UTF-8

withCString :: Text -> (CString -> IO a) -> IO a Source #

Marshal a Text into a C string with a trailing NUL byte, encoded as UTF-8 in temporary storage.

The temporary storage 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 function returns.

Since: 2.0.1

peekCStringLen :: CStringLen -> IO Text Source #

O(n) Decode a C string with explicit length, which is assumed to have been encoded as UTF-8. If decoding fails, a UnicodeException is thrown.

Since: 1.0.0.0

withCStringLen :: Text -> (CStringLen -> IO a) -> IO a Source #

Marshal a Text into a C string encoded as UTF-8 in temporary storage, with explicit length information. The encoded string may contain NUL bytes, and is not followed by a trailing NUL byte.

The temporary storage 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 function returns.

Since: 1.0.0.0

Unsafe conversion code

lengthWord8 :: Text -> Int Source #

O(1) Return the length of a Text in units of Word8. This is useful for sizing a target array appropriately before using unsafeCopyToPtr.

Since: 2.0

unsafeCopyToPtr :: Text -> Ptr Word8 -> IO () Source #

O(n) Copy a Text to an array. The array is assumed to be big enough to hold the contents of the entire Text.

Low-level manipulation

Foreign functions that use UTF-8 internally may return indices in units of Word8 instead of characters. These functions may safely be used with such indices, as they will adjust offsets if necessary to preserve the validity of a Unicode string.

dropWord8 :: I8 -> Text -> Text Source #

O(1) Return the suffix of the Text, with n Word8 units dropped from its beginning.

If n would cause the Text to begin inside a code point, the beginning of the suffix will be advanced by several additional Word8 unit to maintain its validity.

Since: 2.0

takeWord8 :: I8 -> Text -> Text Source #

O(1) Return the prefix of the Text of n Word8 units in length.

If n would cause the Text to end inside a code point, the end of the prefix will be advanced by several additional Word8 units to maintain its validity.

Since: 2.0