base-4.9.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.

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 # 
Enum CChar # 
Eq CChar # 

Methods

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

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

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

newtype CSChar Source #

Haskell type representing the C signed char type.

Constructors

CSChar Int8 

Instances

Bounded CSChar # 
Enum CSChar # 
Eq CSChar # 
Integral CSChar # 
Num CSChar # 
Ord CSChar # 
Read CSChar # 
Real CSChar # 
Show CSChar # 
FiniteBits CSChar # 
Bits CSChar # 
Storable CSChar # 

newtype CUChar Source #

Haskell type representing the C unsigned char type.

Constructors

CUChar Word8 

Instances

Bounded CUChar # 
Enum CUChar # 
Eq CUChar # 
Integral CUChar # 
Num CUChar # 
Ord CUChar # 
Read CUChar # 
Real CUChar # 
Show CUChar # 
FiniteBits CUChar # 
Bits CUChar # 
Storable CUChar # 

newtype CShort Source #

Haskell type representing the C short type.

Constructors

CShort Int16 

Instances

Bounded CShort # 
Enum CShort # 
Eq CShort # 
Integral CShort # 
Num CShort # 
Ord CShort # 
Read CShort # 
Real CShort # 
Show CShort # 
FiniteBits CShort # 
Bits CShort # 
Storable CShort # 

newtype CUShort Source #

Haskell type representing the C unsigned short type.

Constructors

CUShort Word16 

Instances

Bounded CUShort # 
Enum CUShort # 
Eq CUShort # 
Integral CUShort # 
Num CUShort # 
Ord CUShort # 
Read CUShort # 
Real CUShort # 
Show CUShort # 
FiniteBits CUShort # 
Bits CUShort # 
Storable CUShort # 

newtype CInt Source #

Haskell type representing the C int type.

Constructors

CInt Int32 

Instances

Bounded CInt # 
Enum CInt # 
Eq CInt # 

Methods

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

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

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

newtype CUInt Source #

Haskell type representing the C unsigned int type.

Constructors

CUInt Word32 

Instances

Bounded CUInt # 
Enum CUInt # 
Eq CUInt # 

Methods

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

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

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

newtype CLong Source #

Haskell type representing the C long type.

Constructors

CLong Int64 

Instances

Bounded CLong # 
Enum CLong # 
Eq CLong # 

Methods

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

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

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

newtype CULong Source #

Haskell type representing the C unsigned long type.

Constructors

CULong Word64 

Instances

Bounded CULong # 
Enum CULong # 
Eq CULong # 
Integral CULong # 
Num CULong # 
Ord CULong # 
Read CULong # 
Real CULong # 
Show CULong # 
FiniteBits CULong # 
Bits CULong # 
Storable CULong # 

newtype CPtrdiff Source #

Haskell type representing the C ptrdiff_t type.

Constructors

CPtrdiff Int64 

Instances

Bounded CPtrdiff # 
Enum CPtrdiff # 
Eq CPtrdiff # 
Integral CPtrdiff # 
Num CPtrdiff # 
Ord CPtrdiff # 
Read CPtrdiff # 
Real CPtrdiff # 
Show CPtrdiff # 
FiniteBits CPtrdiff # 
Bits CPtrdiff # 
Storable CPtrdiff # 

newtype CSize Source #

Haskell type representing the C size_t type.

Constructors

CSize Word64 

Instances

Bounded CSize # 
Enum CSize # 
Eq CSize # 

Methods

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

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

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

newtype CWchar Source #

Haskell type representing the C wchar_t type.

Constructors

CWchar Int32 

Instances

Bounded CWchar # 
Enum CWchar # 
Eq CWchar # 
Integral CWchar # 
Num CWchar # 
Ord CWchar # 
Read CWchar # 
Real CWchar # 
Show CWchar # 
FiniteBits CWchar # 
Bits CWchar # 
Storable CWchar # 

newtype CSigAtomic Source #

Haskell type representing the C sig_atomic_t type.

Constructors

CSigAtomic Int32 

Instances

Bounded CSigAtomic # 
Enum CSigAtomic # 
Eq CSigAtomic # 
Integral CSigAtomic # 
Num CSigAtomic # 
Ord CSigAtomic # 
Read CSigAtomic # 
Real CSigAtomic # 
Show CSigAtomic # 
FiniteBits CSigAtomic # 
Bits CSigAtomic # 
Storable CSigAtomic # 

newtype CLLong Source #

Haskell type representing the C long long type.

Constructors

CLLong Int64 

Instances

Bounded CLLong # 
Enum CLLong # 
Eq CLLong # 
Integral CLLong # 
Num CLLong # 
Ord CLLong # 
Read CLLong # 
Real CLLong # 
Show CLLong # 
FiniteBits CLLong # 
Bits CLLong # 
Storable CLLong # 

newtype CULLong Source #

Haskell type representing the C unsigned long long type.

Constructors

CULLong Word64 

Instances

Bounded CULLong # 
Enum CULLong # 
Eq CULLong # 
Integral CULLong # 
Num CULLong # 
Ord CULLong # 
Read CULLong # 
Real CULLong # 
Show CULLong # 
FiniteBits CULLong # 
Bits CULLong # 
Storable CULLong # 

newtype CIntPtr Source #

Constructors

CIntPtr Int64 

Instances

Bounded CIntPtr # 
Enum CIntPtr # 
Eq CIntPtr # 
Integral CIntPtr # 
Num CIntPtr # 
Ord CIntPtr # 
Read CIntPtr # 
Real CIntPtr # 
Show CIntPtr # 
FiniteBits CIntPtr # 
Bits CIntPtr # 
Storable CIntPtr # 

newtype CUIntPtr Source #

Constructors

CUIntPtr Word64 

Instances

Bounded CUIntPtr # 
Enum CUIntPtr # 
Eq CUIntPtr # 
Integral CUIntPtr # 
Num CUIntPtr # 
Ord CUIntPtr # 
Read CUIntPtr # 
Real CUIntPtr # 
Show CUIntPtr # 
FiniteBits CUIntPtr # 
Bits CUIntPtr # 
Storable CUIntPtr # 

newtype CIntMax Source #

Constructors

CIntMax Int64 

Instances

Bounded CIntMax # 
Enum CIntMax # 
Eq CIntMax # 
Integral CIntMax # 
Num CIntMax # 
Ord CIntMax # 
Read CIntMax # 
Real CIntMax # 
Show CIntMax # 
FiniteBits CIntMax # 
Bits CIntMax # 
Storable CIntMax # 

newtype CUIntMax Source #

Constructors

CUIntMax Word64 

Instances

Bounded CUIntMax # 
Enum CUIntMax # 
Eq CUIntMax # 
Integral CUIntMax # 
Num CUIntMax # 
Ord CUIntMax # 
Read CUIntMax # 
Real CUIntMax # 
Show CUIntMax # 
FiniteBits CUIntMax # 
Bits CUIntMax # 
Storable CUIntMax # 

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 # 
Eq CClock # 
Num CClock # 
Ord CClock # 
Read CClock # 
Real CClock # 
Show CClock # 
Storable CClock # 

newtype CTime Source #

Haskell type representing the C time_t type.

Constructors

CTime Int64 

Instances

Enum CTime # 
Eq CTime # 

Methods

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

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

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

newtype CUSeconds Source #

Haskell type representing the C useconds_t type.

Since: 4.4.0.0

Constructors

CUSeconds Word32 

Instances

Enum CUSeconds # 
Eq CUSeconds # 
Num CUSeconds # 
Ord CUSeconds # 
Read CUSeconds # 
Real CUSeconds # 
Show CUSeconds # 
Storable CUSeconds # 

newtype CSUSeconds Source #

Haskell type representing the C suseconds_t type.

Since: 4.4.0.0

Constructors

CSUSeconds Int64 

Instances

Enum CSUSeconds # 
Eq CSUSeconds # 
Num CSUSeconds # 
Ord CSUSeconds # 
Read CSUSeconds # 
Real CSUSeconds # 
Show CSUSeconds # 
Storable CSUSeconds # 

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 # 
Eq CFloat # 
Floating CFloat # 
Fractional CFloat # 
Num CFloat # 
Ord CFloat # 
Read CFloat # 
Real CFloat # 
RealFloat CFloat # 
RealFrac CFloat # 
Show CFloat # 
Storable CFloat # 

newtype CDouble Source #

Haskell type representing the C double type.

Constructors

CDouble Double 

Instances

Enum CDouble # 
Eq CDouble # 
Floating CDouble # 
Fractional CDouble # 
Num CDouble # 
Ord CDouble # 
Read CDouble # 
Real CDouble # 
RealFloat CDouble # 
RealFrac CDouble # 
Show CDouble # 
Storable CDouble # 

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.