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 | Safe-Inferred |
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
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.)
See Note [Lack of signals on wasm32-wasi].
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
Haskell type representing the C time_t
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Enum CTime Source # | |
Defined in GHC.Internal.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 # | |
Storable CTime Source # | |
Defined in GHC.Internal.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 # | |
Num CTime Source # | |
Read CTime Source # | |
Real CTime Source # | |
Defined in GHC.Internal.Foreign.C.Types toRational :: CTime -> Rational Source # | |
Show CTime Source # | |
Eq CTime Source # | |
Ord CTime Source # | |
Defined in GHC.Internal.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.)