base-4.11.0.0: Basic libraries

Copyright(c) The FFI task force 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerffi@haskell.org
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Foreign.C.Types

Contents

Description

Mapping of C types to corresponding Haskell types.

Synopsis

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 of CT 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 for CT has a valid representation in C.
  • sizeOf (undefined :: CT) will yield the same value as sizeof (t) in C.
  • alignment (undefined :: CT) matches the alignment constraint enforced by the C implementation for t.
  • The members peek and poke of the Storable class map all values of CT to the corresponding value of t and vice versa.
  • When an instance of Bounded is defined for CT, the values of minBound and maxBound coincide with t_MIN and t_MAX in C.
  • When an instance of Eq or Ord is defined for CT, the predicates defined by the type class implement the same relation as the corresponding predicate in C on t.
  • When an instance of Num, Read, Integral, Fractional, Floating, RealFrac, or RealFloat is defined for CT, the arithmetic operations defined by the type class implement the same function as the corresponding arithmetic operations (if available) in C on t.
  • When an instance of Bits is defined for CT, the bitwise operation defined by the type class implement the same function as the corresponding bitwise operation in C on t.

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

newtype CChar Source #

Haskell type representing the C char type.

Constructors

CChar Int8 
Instances
Bounded CChar # 
Instance details
Enum CChar # 
Instance details
Eq CChar # 
Instance details

Methods

(==) :: CChar -> CChar -> Bool Source #

(/=) :: CChar -> CChar -> Bool Source #

Integral CChar # 
Instance details
Num CChar # 
Instance details
Ord CChar # 
Instance details
Read CChar # 
Instance details
Real CChar # 
Instance details
Show CChar # 
Instance details
FiniteBits CChar # 
Instance details
Bits CChar # 
Instance details
Storable CChar # 
Instance details

newtype CSChar Source #

Haskell type representing the C signed char type.

Constructors

CSChar Int8 
Instances
Bounded CSChar # 
Instance details
Enum CSChar # 
Instance details
Eq CSChar # 
Instance details
Integral CSChar # 
Instance details
Num CSChar # 
Instance details
Ord CSChar # 
Instance details
Read CSChar # 
Instance details
Real CSChar # 
Instance details
Show CSChar # 
Instance details
FiniteBits CSChar # 
Instance details
Bits CSChar # 
Instance details
Storable CSChar # 
Instance details

newtype CUChar Source #

Haskell type representing the C unsigned char type.

Constructors

CUChar Word8 
Instances
Bounded CUChar # 
Instance details
Enum CUChar # 
Instance details
Eq CUChar # 
Instance details
Integral CUChar # 
Instance details
Num CUChar # 
Instance details
Ord CUChar # 
Instance details
Read CUChar # 
Instance details
Real CUChar # 
Instance details
Show CUChar # 
Instance details
FiniteBits CUChar # 
Instance details
Bits CUChar # 
Instance details
Storable CUChar # 
Instance details

newtype CShort Source #

Haskell type representing the C short type.

Constructors

CShort Int16 
Instances
Bounded CShort # 
Instance details
Enum CShort # 
Instance details
Eq CShort # 
Instance details
Integral CShort # 
Instance details
Num CShort # 
Instance details
Ord CShort # 
Instance details
Read CShort # 
Instance details
Real CShort # 
Instance details
Show CShort # 
Instance details
FiniteBits CShort # 
Instance details
Bits CShort # 
Instance details
Storable CShort # 
Instance details

newtype CUShort Source #

Haskell type representing the C unsigned short type.

Constructors

CUShort Word16 
Instances
Bounded CUShort # 
Instance details
Enum CUShort # 
Instance details
Eq CUShort # 
Instance details
Integral CUShort # 
Instance details
Num CUShort # 
Instance details
Ord CUShort # 
Instance details
Read CUShort # 
Instance details
Real CUShort # 
Instance details
Show CUShort # 
Instance details
FiniteBits CUShort # 
Instance details
Bits CUShort # 
Instance details
Storable CUShort # 
Instance details

newtype CInt Source #

Haskell type representing the C int type.

Constructors

CInt Int32 
Instances
Bounded CInt # 
Instance details
Enum CInt # 
Instance details
Eq CInt # 
Instance details

Methods

(==) :: CInt -> CInt -> Bool Source #

(/=) :: CInt -> CInt -> Bool Source #

Integral CInt # 
Instance details
Num CInt # 
Instance details
Ord CInt # 
Instance details
Read CInt # 
Instance details
Real CInt # 
Instance details
Show CInt # 
Instance details
FiniteBits CInt # 
Instance details
Bits CInt # 
Instance details
Storable CInt # 
Instance details

newtype CUInt Source #

Haskell type representing the C unsigned int type.

Constructors

CUInt Word32 
Instances
Bounded CUInt # 
Instance details
Enum CUInt # 
Instance details
Eq CUInt # 
Instance details

Methods

(==) :: CUInt -> CUInt -> Bool Source #

(/=) :: CUInt -> CUInt -> Bool Source #

Integral CUInt # 
Instance details
Num CUInt # 
Instance details
Ord CUInt # 
Instance details
Read CUInt # 
Instance details
Real CUInt # 
Instance details
Show CUInt # 
Instance details
FiniteBits CUInt # 
Instance details
Bits CUInt # 
Instance details
Storable CUInt # 
Instance details

newtype CLong Source #

Haskell type representing the C long type.

Constructors

CLong Int64 
Instances
Bounded CLong # 
Instance details
Enum CLong # 
Instance details
Eq CLong # 
Instance details

Methods

(==) :: CLong -> CLong -> Bool Source #

(/=) :: CLong -> CLong -> Bool Source #

Integral CLong # 
Instance details
Num CLong # 
Instance details
Ord CLong # 
Instance details
Read CLong # 
Instance details
Real CLong # 
Instance details
Show CLong # 
Instance details
FiniteBits CLong # 
Instance details
Bits CLong # 
Instance details
Storable CLong # 
Instance details

newtype CULong Source #

Haskell type representing the C unsigned long type.

Constructors

CULong Word64 
Instances
Bounded CULong # 
Instance details
Enum CULong # 
Instance details
Eq CULong # 
Instance details
Integral CULong # 
Instance details
Num CULong # 
Instance details
Ord CULong # 
Instance details
Read CULong # 
Instance details
Real CULong # 
Instance details
Show CULong # 
Instance details
FiniteBits CULong # 
Instance details
Bits CULong # 
Instance details
Storable CULong # 
Instance details

newtype CPtrdiff Source #

Haskell type representing the C ptrdiff_t type.

Constructors

CPtrdiff Int64 
Instances
Bounded CPtrdiff # 
Instance details
Enum CPtrdiff # 
Instance details
Eq CPtrdiff # 
Instance details
Integral CPtrdiff # 
Instance details
Num CPtrdiff # 
Instance details
Ord CPtrdiff # 
Instance details
Read CPtrdiff # 
Instance details
Real CPtrdiff # 
Instance details
Show CPtrdiff # 
Instance details
FiniteBits CPtrdiff # 
Instance details
Bits CPtrdiff # 
Instance details
Storable CPtrdiff # 
Instance details

newtype CSize Source #

Haskell type representing the C size_t type.

Constructors

CSize Word64 
Instances
Bounded CSize # 
Instance details
Enum CSize # 
Instance details
Eq CSize # 
Instance details

Methods

(==) :: CSize -> CSize -> Bool Source #

(/=) :: CSize -> CSize -> Bool Source #

Integral CSize # 
Instance details
Num CSize # 
Instance details
Ord CSize # 
Instance details
Read CSize # 
Instance details
Real CSize # 
Instance details
Show CSize # 
Instance details
FiniteBits CSize # 
Instance details
Bits CSize # 
Instance details
Storable CSize # 
Instance details

newtype CWchar Source #

Haskell type representing the C wchar_t type.

Constructors

CWchar Int32 
Instances
Bounded CWchar # 
Instance details
Enum CWchar # 
Instance details
Eq CWchar # 
Instance details
Integral CWchar # 
Instance details
Num CWchar # 
Instance details
Ord CWchar # 
Instance details
Read CWchar # 
Instance details
Real CWchar # 
Instance details
Show CWchar # 
Instance details
FiniteBits CWchar # 
Instance details
Bits CWchar # 
Instance details
Storable CWchar # 
Instance details

newtype CSigAtomic Source #

Haskell type representing the C sig_atomic_t type.

Constructors

CSigAtomic Int32 
Instances
Bounded CSigAtomic # 
Instance details
Enum CSigAtomic # 
Instance details
Eq CSigAtomic # 
Instance details
Integral CSigAtomic # 
Instance details
Num CSigAtomic # 
Instance details
Ord CSigAtomic # 
Instance details
Read CSigAtomic # 
Instance details
Real CSigAtomic # 
Instance details
Show CSigAtomic # 
Instance details
FiniteBits CSigAtomic # 
Instance details
Bits CSigAtomic # 
Instance details
Storable CSigAtomic # 
Instance details

newtype CLLong Source #

Haskell type representing the C long long type.

Constructors

CLLong Int64 
Instances
Bounded CLLong # 
Instance details
Enum CLLong # 
Instance details
Eq CLLong # 
Instance details
Integral CLLong # 
Instance details
Num CLLong # 
Instance details
Ord CLLong # 
Instance details
Read CLLong # 
Instance details
Real CLLong # 
Instance details
Show CLLong # 
Instance details
FiniteBits CLLong # 
Instance details
Bits CLLong # 
Instance details
Storable CLLong # 
Instance details

newtype CULLong Source #

Haskell type representing the C unsigned long long type.

Constructors

CULLong Word64 
Instances
Bounded CULLong # 
Instance details
Enum CULLong # 
Instance details
Eq CULLong # 
Instance details
Integral CULLong # 
Instance details
Num CULLong # 
Instance details
Ord CULLong # 
Instance details
Read CULLong # 
Instance details
Real CULLong # 
Instance details
Show CULLong # 
Instance details
FiniteBits CULLong # 
Instance details
Bits CULLong # 
Instance details
Storable CULLong # 
Instance details

newtype CBool Source #

Haskell type representing the C bool type.

Since: 4.10.0.0

Constructors

CBool Word8 
Instances
Bounded CBool # 
Instance details
Enum CBool # 
Instance details
Eq CBool # 
Instance details

Methods

(==) :: CBool -> CBool -> Bool Source #

(/=) :: CBool -> CBool -> Bool Source #

Integral CBool # 
Instance details
Num CBool # 
Instance details
Ord CBool # 
Instance details
Read CBool # 
Instance details
Real CBool # 
Instance details
Show CBool # 
Instance details
FiniteBits CBool # 
Instance details
Bits CBool # 
Instance details
Storable CBool # 
Instance details

newtype CIntPtr Source #

Constructors

CIntPtr Int64 
Instances
Bounded CIntPtr # 
Instance details
Enum CIntPtr # 
Instance details
Eq CIntPtr # 
Instance details
Integral CIntPtr # 
Instance details
Num CIntPtr # 
Instance details
Ord CIntPtr # 
Instance details
Read CIntPtr # 
Instance details
Real CIntPtr # 
Instance details
Show CIntPtr # 
Instance details
FiniteBits CIntPtr # 
Instance details
Bits CIntPtr # 
Instance details
Storable CIntPtr # 
Instance details

newtype CUIntPtr Source #

Constructors

CUIntPtr Word64 
Instances
Bounded CUIntPtr # 
Instance details
Enum CUIntPtr # 
Instance details
Eq CUIntPtr # 
Instance details
Integral CUIntPtr # 
Instance details
Num CUIntPtr # 
Instance details
Ord CUIntPtr # 
Instance details
Read CUIntPtr # 
Instance details
Real CUIntPtr # 
Instance details
Show CUIntPtr # 
Instance details
FiniteBits CUIntPtr # 
Instance details
Bits CUIntPtr # 
Instance details
Storable CUIntPtr # 
Instance details

newtype CIntMax Source #

Constructors

CIntMax Int64 
Instances
Bounded CIntMax # 
Instance details
Enum CIntMax # 
Instance details
Eq CIntMax # 
Instance details
Integral CIntMax # 
Instance details
Num CIntMax # 
Instance details
Ord CIntMax # 
Instance details
Read CIntMax # 
Instance details
Real CIntMax # 
Instance details
Show CIntMax # 
Instance details
FiniteBits CIntMax # 
Instance details
Bits CIntMax # 
Instance details
Storable CIntMax # 
Instance details

newtype CUIntMax Source #

Constructors

CUIntMax Word64 
Instances
Bounded CUIntMax # 
Instance details
Enum CUIntMax # 
Instance details
Eq CUIntMax # 
Instance details
Integral CUIntMax # 
Instance details
Num CUIntMax # 
Instance details
Ord CUIntMax # 
Instance details
Read CUIntMax # 
Instance details
Real CUIntMax # 
Instance details
Show CUIntMax # 
Instance details
FiniteBits CUIntMax # 
Instance details
Bits CUIntMax # 
Instance details
Storable CUIntMax # 
Instance details

Numeric types

These types are represented as newtypes of basic foreign types, and are instances of Eq, Ord, Num, Read, Show, Enum, Typeable and Storable.

newtype CClock Source #

Haskell type representing the C clock_t type.

Constructors

CClock Int64 
Instances
Enum CClock # 
Instance details
Eq CClock # 
Instance details
Num CClock # 
Instance details
Ord CClock # 
Instance details
Read CClock # 
Instance details
Real CClock # 
Instance details
Show CClock # 
Instance details
Storable CClock # 
Instance details

newtype CTime Source #

Haskell type representing the C time_t type.

Constructors

CTime Int64 
Instances
Enum CTime # 
Instance details
Eq CTime # 
Instance details

Methods

(==) :: CTime -> CTime -> Bool Source #

(/=) :: CTime -> CTime -> Bool Source #

Num CTime # 
Instance details
Ord CTime # 
Instance details
Read CTime # 
Instance details
Real CTime # 
Instance details
Show CTime # 
Instance details
Storable CTime # 
Instance details

newtype CUSeconds Source #

Haskell type representing the C useconds_t type.

Since: 4.4.0.0

Constructors

CUSeconds Word32 
Instances
Enum CUSeconds # 
Instance details
Eq CUSeconds # 
Instance details
Num CUSeconds # 
Instance details
Ord CUSeconds # 
Instance details
Read CUSeconds # 
Instance details
Real CUSeconds # 
Instance details
Show CUSeconds # 
Instance details
Storable CUSeconds # 
Instance details

newtype CSUSeconds Source #

Haskell type representing the C suseconds_t type.

Since: 4.4.0.0

Constructors

CSUSeconds Int64 
Instances
Enum CSUSeconds # 
Instance details
Eq CSUSeconds # 
Instance details
Num CSUSeconds # 
Instance details
Ord CSUSeconds # 
Instance details
Read CSUSeconds # 
Instance details
Real CSUSeconds # 
Instance details
Show CSUSeconds # 
Instance details
Storable CSUSeconds # 
Instance details

To convert CTime to UTCTime, use the following:

\t -> posixSecondsToUTCTime (realToFrac t :: POSIXTime)

Floating types

These types are represented as newtypes of Float and Double, and are instances of Eq, Ord, Num, Read, Show, Enum, Typeable, Storable, Real, Fractional, Floating, RealFrac and RealFloat.

newtype CFloat Source #

Haskell type representing the C float type.

Constructors

CFloat Float 
Instances
Enum CFloat # 
Instance details
Eq CFloat # 
Instance details
Floating CFloat # 
Instance details
Fractional CFloat # 
Instance details
Num CFloat # 
Instance details
Ord CFloat # 
Instance details
Read CFloat # 
Instance details
Real CFloat # 
Instance details
RealFloat CFloat # 
Instance details
RealFrac CFloat # 
Instance details
Show CFloat # 
Instance details
Storable CFloat # 
Instance details

newtype CDouble Source #

Haskell type representing the C double type.

Constructors

CDouble Double 
Instances
Enum CDouble # 
Instance details
Eq CDouble # 
Instance details
Floating CDouble # 
Instance details
Fractional CDouble # 
Instance details
Num CDouble # 
Instance details
Ord CDouble # 
Instance details
Read CDouble # 
Instance details
Real CDouble # 
Instance details
RealFloat CDouble # 
Instance details
RealFrac CDouble # 
Instance details
Show CDouble # 
Instance details
Storable CDouble # 
Instance details

Other types

data CFile Source #

Haskell type representing the C FILE type.

data CFpos Source #

Haskell type representing the C fpos_t type.

data CJmpBuf Source #

Haskell type representing the C jmp_buf type.