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.
Synopsis
- 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 CBool = CBool Word8
- 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
.
Platform differences
This module contains platform specific information about types. As such, the types presented on this page reflect the platform on which the documentation was generated and may not coincide with the types on your platform.
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.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C signed char
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C unsigned char
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C short
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C unsigned short
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C int
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C unsigned int
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C long
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C unsigned long
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C ptrdiff_t
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C size_t
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C wchar_t
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
newtype CSigAtomic Source #
Haskell type representing the C sig_atomic_t
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C long long
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C unsigned long long
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C bool
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Since: base-4.10.0.0
Instances
Instances
Instances
Instances
Instances
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.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Storable CClock Source # | |
Defined in Foreign.C.Types 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 # | |
Enum CClock Source # | |
Defined in Foreign.C.Types 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 # | |
Num CClock Source # | |
Read CClock Source # | |
Real CClock Source # | |
Defined in Foreign.C.Types toRational :: CClock -> Rational Source # | |
Show CClock Source # | |
Eq CClock Source # | |
Ord CClock Source # | |
Defined in Foreign.C.Types |
Haskell type representing the C time_t
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Storable CTime Source # | |
Defined in Foreign.C.Types sizeOf :: CTime -> Int Source # alignment :: CTime -> Int Source # peekElemOff :: Ptr CTime -> Int -> IO CTime Source # pokeElemOff :: Ptr CTime -> Int -> CTime -> IO () Source # peekByteOff :: Ptr b -> Int -> IO CTime Source # pokeByteOff :: Ptr b -> Int -> CTime -> IO () Source # | |
Enum CTime Source # | |
Defined in Foreign.C.Types succ :: CTime -> CTime Source # pred :: CTime -> CTime Source # toEnum :: Int -> CTime Source # fromEnum :: CTime -> Int Source # enumFrom :: CTime -> [CTime] Source # enumFromThen :: CTime -> CTime -> [CTime] Source # enumFromTo :: CTime -> CTime -> [CTime] Source # enumFromThenTo :: CTime -> CTime -> CTime -> [CTime] Source # | |
Num CTime Source # | |
Read CTime Source # | |
Real CTime Source # | |
Defined in Foreign.C.Types toRational :: CTime -> Rational Source # | |
Show CTime Source # | |
Eq CTime Source # | |
Ord CTime Source # | |
Defined in Foreign.C.Types |
Haskell type representing the C useconds_t
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Since: base-4.4.0.0
Instances
newtype CSUSeconds Source #
Haskell type representing the C suseconds_t
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Since: base-4.4.0.0
Instances
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
. That does mean
that CFloat
's (respectively CDouble
's) instances of
Eq
, Ord
, Num
and
Fractional
are as badly behaved as Float
's
(respectively Double
's).
Haskell type representing the C float
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C double
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Other types
Haskell type representing the C FILE
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Haskell type representing the C fpos_t
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Haskell type representing the C jmp_buf
type.
(The concrete types of Foreign.C.Types are platform-specific.)