Copyright | (c) The FFI task force 2001 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | ffi@haskell.org |
Stability | provisional |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Mapping of C types to corresponding Haskell types.
- newtype CChar = CChar Int8
- newtype CSChar = CSChar Int8
- newtype CUChar = CUChar Word8
- newtype CShort = CShort Int16
- newtype CUShort = CUShort Word16
- newtype CInt = CInt Int32
- newtype CUInt = CUInt Word32
- newtype CLong = CLong Int64
- newtype CULong = CULong Word64
- newtype CPtrdiff = CPtrdiff Int64
- newtype CSize = CSize Word64
- newtype CWchar = CWchar Int32
- newtype CSigAtomic = CSigAtomic Int32
- newtype CLLong = CLLong Int64
- newtype CULLong = CULLong Word64
- newtype CIntPtr = CIntPtr Int64
- newtype CUIntPtr = CUIntPtr Word64
- newtype CIntMax = CIntMax Int64
- newtype CUIntMax = CUIntMax Word64
- newtype CClock = CClock Int64
- newtype CTime = CTime Int64
- newtype CUSeconds = CUSeconds Word32
- newtype CSUSeconds = CSUSeconds Int64
- newtype CFloat = CFloat Float
- newtype CDouble = CDouble Double
- data CFile
- data CFpos
- data CJmpBuf
Representations of C types
These types are needed to accurately represent C function prototypes,
in order to access C library interfaces in Haskell. The Haskell system
is not required to represent those types exactly as C does, but the
following guarantees are provided concerning a Haskell type CT
representing a C type t
:
- If a C function prototype has
t
as an argument or result type, the use ofCT
in the corresponding position in a foreign declaration permits the Haskell program to access the full range of values encoded by the C type; and conversely, any Haskell value forCT
has a valid representation in C.
will yield the same value assizeOf
(undefined
:: CT)sizeof (t)
in C.
matches the alignment constraint enforced by the C implementation foralignment
(undefined
:: CT)t
.- The members
peek
andpoke
of theStorable
class map all values ofCT
to the corresponding value oft
and vice versa. - When an instance of
Bounded
is defined forCT
, the values ofminBound
andmaxBound
coincide witht_MIN
andt_MAX
in C. - When an instance of
Eq
orOrd
is defined forCT
, the predicates defined by the type class implement the same relation as the corresponding predicate in C ont
. - When an instance of
Num
,Read
,Integral
,Fractional
,Floating
,RealFrac
, orRealFloat
is defined forCT
, the arithmetic operations defined by the type class implement the same function as the corresponding arithmetic operations (if available) in C ont
. - When an instance of
Bits
is defined forCT
, the bitwise operation defined by the type class implement the same function as the corresponding bitwise operation in C ont
.
Integral types
These types are represented as newtype
s of
types in Data.Int and Data.Word, and are instances of
Eq
, Ord
, Num
, Read
,
Show
, Enum
, Typeable
, Storable
,
Bounded
, Real
, Integral
and
Bits
.
Haskell type representing the C char
type.
Bounded CChar | |
Enum CChar | |
Eq CChar | |
Integral CChar | |
Num CChar | |
Ord CChar | |
Read CChar | |
Real CChar | |
toRational :: CChar -> Rational Source | |
Show CChar | |
FiniteBits CChar | |
finiteBitSize :: CChar -> Int Source countLeadingZeros :: CChar -> Int Source countTrailingZeros :: CChar -> Int Source | |
Bits CChar | |
(.&.) :: CChar -> CChar -> CChar Source (.|.) :: CChar -> CChar -> CChar Source xor :: CChar -> CChar -> CChar Source complement :: CChar -> CChar Source shift :: CChar -> Int -> CChar Source rotate :: CChar -> Int -> CChar Source setBit :: CChar -> Int -> CChar Source clearBit :: CChar -> Int -> CChar Source complementBit :: CChar -> Int -> CChar Source testBit :: CChar -> Int -> Bool Source bitSizeMaybe :: CChar -> Maybe Int Source bitSize :: CChar -> Int Source isSigned :: CChar -> Bool Source shiftL :: CChar -> Int -> CChar Source unsafeShiftL :: CChar -> Int -> CChar Source shiftR :: CChar -> Int -> CChar Source unsafeShiftR :: CChar -> Int -> CChar Source rotateL :: CChar -> Int -> CChar Source | |
Storable CChar | |
Haskell type representing the C signed char
type.
Haskell type representing the C unsigned char
type.
Haskell type representing the C short
type.
Haskell type representing the C unsigned short
type.
Haskell type representing the C int
type.
Bounded CInt | |
Enum CInt | |
Eq CInt | |
Integral CInt | |
Num CInt | |
Ord CInt | |
Read CInt | |
Real CInt | |
toRational :: CInt -> Rational Source | |
Show CInt | |
FiniteBits CInt | |
finiteBitSize :: CInt -> Int Source countLeadingZeros :: CInt -> Int Source countTrailingZeros :: CInt -> Int Source | |
Bits CInt | |
(.&.) :: CInt -> CInt -> CInt Source (.|.) :: CInt -> CInt -> CInt Source xor :: CInt -> CInt -> CInt Source complement :: CInt -> CInt Source shift :: CInt -> Int -> CInt Source rotate :: CInt -> Int -> CInt Source setBit :: CInt -> Int -> CInt Source clearBit :: CInt -> Int -> CInt Source complementBit :: CInt -> Int -> CInt Source testBit :: CInt -> Int -> Bool Source bitSizeMaybe :: CInt -> Maybe Int Source isSigned :: CInt -> Bool Source shiftL :: CInt -> Int -> CInt Source unsafeShiftL :: CInt -> Int -> CInt Source shiftR :: CInt -> Int -> CInt Source unsafeShiftR :: CInt -> Int -> CInt Source rotateL :: CInt -> Int -> CInt Source | |
Storable CInt | |
Haskell type representing the C unsigned int
type.
Bounded CUInt | |
Enum CUInt | |
Eq CUInt | |
Integral CUInt | |
Num CUInt | |
Ord CUInt | |
Read CUInt | |
Real CUInt | |
toRational :: CUInt -> Rational Source | |
Show CUInt | |
FiniteBits CUInt | |
finiteBitSize :: CUInt -> Int Source countLeadingZeros :: CUInt -> Int Source countTrailingZeros :: CUInt -> Int Source | |
Bits CUInt | |
(.&.) :: CUInt -> CUInt -> CUInt Source (.|.) :: CUInt -> CUInt -> CUInt Source xor :: CUInt -> CUInt -> CUInt Source complement :: CUInt -> CUInt Source shift :: CUInt -> Int -> CUInt Source rotate :: CUInt -> Int -> CUInt Source setBit :: CUInt -> Int -> CUInt Source clearBit :: CUInt -> Int -> CUInt Source complementBit :: CUInt -> Int -> CUInt Source testBit :: CUInt -> Int -> Bool Source bitSizeMaybe :: CUInt -> Maybe Int Source bitSize :: CUInt -> Int Source isSigned :: CUInt -> Bool Source shiftL :: CUInt -> Int -> CUInt Source unsafeShiftL :: CUInt -> Int -> CUInt Source shiftR :: CUInt -> Int -> CUInt Source unsafeShiftR :: CUInt -> Int -> CUInt Source rotateL :: CUInt -> Int -> CUInt Source | |
Storable CUInt | |
Haskell type representing the C long
type.
Bounded CLong | |
Enum CLong | |
Eq CLong | |
Integral CLong | |
Num CLong | |
Ord CLong | |
Read CLong | |
Real CLong | |
toRational :: CLong -> Rational Source | |
Show CLong | |
FiniteBits CLong | |
finiteBitSize :: CLong -> Int Source countLeadingZeros :: CLong -> Int Source countTrailingZeros :: CLong -> Int Source | |
Bits CLong | |
(.&.) :: CLong -> CLong -> CLong Source (.|.) :: CLong -> CLong -> CLong Source xor :: CLong -> CLong -> CLong Source complement :: CLong -> CLong Source shift :: CLong -> Int -> CLong Source rotate :: CLong -> Int -> CLong Source setBit :: CLong -> Int -> CLong Source clearBit :: CLong -> Int -> CLong Source complementBit :: CLong -> Int -> CLong Source testBit :: CLong -> Int -> Bool Source bitSizeMaybe :: CLong -> Maybe Int Source bitSize :: CLong -> Int Source isSigned :: CLong -> Bool Source shiftL :: CLong -> Int -> CLong Source unsafeShiftL :: CLong -> Int -> CLong Source shiftR :: CLong -> Int -> CLong Source unsafeShiftR :: CLong -> Int -> CLong Source rotateL :: CLong -> Int -> CLong Source | |
Storable CLong | |
Haskell type representing the C unsigned long
type.
Haskell type representing the C ptrdiff_t
type.
Haskell type representing the C size_t
type.
Bounded CSize | |
Enum CSize | |
Eq CSize | |
Integral CSize | |
Num CSize | |
Ord CSize | |
Read CSize | |
Real CSize | |
toRational :: CSize -> Rational Source | |
Show CSize | |
FiniteBits CSize | |
finiteBitSize :: CSize -> Int Source countLeadingZeros :: CSize -> Int Source countTrailingZeros :: CSize -> Int Source | |
Bits CSize | |
(.&.) :: CSize -> CSize -> CSize Source (.|.) :: CSize -> CSize -> CSize Source xor :: CSize -> CSize -> CSize Source complement :: CSize -> CSize Source shift :: CSize -> Int -> CSize Source rotate :: CSize -> Int -> CSize Source setBit :: CSize -> Int -> CSize Source clearBit :: CSize -> Int -> CSize Source complementBit :: CSize -> Int -> CSize Source testBit :: CSize -> Int -> Bool Source bitSizeMaybe :: CSize -> Maybe Int Source bitSize :: CSize -> Int Source isSigned :: CSize -> Bool Source shiftL :: CSize -> Int -> CSize Source unsafeShiftL :: CSize -> Int -> CSize Source shiftR :: CSize -> Int -> CSize Source unsafeShiftR :: CSize -> Int -> CSize Source rotateL :: CSize -> Int -> CSize Source | |
Storable CSize | |
Haskell type representing the C wchar_t
type.
newtype CSigAtomic Source
Haskell type representing the C sig_atomic_t
type.
Haskell type representing the C long long
type.
Haskell type representing the C unsigned long long
type.
Numeric types
These types are represented as newtype
s of basic
foreign types, and are instances of
Eq
, Ord
, Num
, Read
,
Show
, Enum
, Typeable
and Storable
.
Haskell type representing the C clock_t
type.
Enum CClock | |
succ :: CClock -> CClock Source pred :: CClock -> CClock Source toEnum :: Int -> CClock Source fromEnum :: CClock -> Int Source enumFrom :: CClock -> [CClock] Source enumFromThen :: CClock -> CClock -> [CClock] Source enumFromTo :: CClock -> CClock -> [CClock] Source enumFromThenTo :: CClock -> CClock -> CClock -> [CClock] Source | |
Eq CClock | |
Num CClock | |
Ord CClock | |
Read CClock | |
Real CClock | |
toRational :: CClock -> Rational Source | |
Show CClock | |
Storable CClock | |
sizeOf :: CClock -> Int Source alignment :: CClock -> Int Source peekElemOff :: Ptr CClock -> Int -> IO CClock Source pokeElemOff :: Ptr CClock -> Int -> CClock -> IO () Source peekByteOff :: Ptr b -> Int -> IO CClock Source pokeByteOff :: Ptr b -> Int -> CClock -> IO () Source |
Haskell type representing the C time_t
type.
Enum CTime | |
Eq CTime | |
Num CTime | |
Ord CTime | |
Read CTime | |
Real CTime | |
toRational :: CTime -> Rational Source | |
Show CTime | |
Storable CTime | |
Haskell type representing the C useconds_t
type.
Since: 4.4.0.0
newtype CSUSeconds Source
Haskell type representing the C suseconds_t
type.
Since: 4.4.0.0
To convert CTime
to UTCTime
, use the following:
\t -> posixSecondsToUTCTime (realToFrac t :: POSIXTime)
Floating types
These types are represented as newtype
s of
Float
and Double
, and are instances of
Eq
, Ord
, Num
, Read
,
Show
, Enum
, Typeable
, Storable
,
Real
, Fractional
, Floating
,
RealFrac
and RealFloat
.
Haskell type representing the C float
type.
Haskell type representing the C double
type.