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

Methods

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

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

Integral CChar Source # 
Num CChar Source # 
Ord CChar Source # 

Methods

compare :: CChar -> CChar -> Ordering #

(<) :: CChar -> CChar -> Bool #

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

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

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

max :: CChar -> CChar -> CChar #

min :: CChar -> CChar -> CChar #

Read CChar Source # 
Real CChar Source # 
Show CChar Source # 
FiniteBits CChar Source # 
Bits CChar Source # 
Storable CChar Source # 

newtype CSChar Source #

Haskell type representing the C signed char type.

Constructors

CSChar Int8 

Instances

Bounded CSChar Source # 
Enum CSChar Source # 
Eq CSChar Source # 

Methods

(==) :: CSChar -> CSChar -> Bool #

(/=) :: CSChar -> CSChar -> Bool #

Integral CSChar Source # 
Num CSChar Source # 
Ord CSChar Source # 
Read CSChar Source # 
Real CSChar Source # 
Show CSChar Source # 
FiniteBits CSChar Source # 
Bits CSChar Source # 
Storable CSChar Source # 

newtype CUChar Source #

Haskell type representing the C unsigned char type.

Constructors

CUChar Word8 

Instances

Bounded CUChar Source # 
Enum CUChar Source # 
Eq CUChar Source # 

Methods

(==) :: CUChar -> CUChar -> Bool #

(/=) :: CUChar -> CUChar -> Bool #

Integral CUChar Source # 
Num CUChar Source # 
Ord CUChar Source # 
Read CUChar Source # 
Real CUChar Source # 
Show CUChar Source # 
FiniteBits CUChar Source # 
Bits CUChar Source # 
Storable CUChar Source # 

newtype CShort Source #

Haskell type representing the C short type.

Constructors

CShort Int16 

Instances

Bounded CShort Source # 
Enum CShort Source # 
Eq CShort Source # 

Methods

(==) :: CShort -> CShort -> Bool #

(/=) :: CShort -> CShort -> Bool #

Integral CShort Source # 
Num CShort Source # 
Ord CShort Source # 
Read CShort Source # 
Real CShort Source # 
Show CShort Source # 
FiniteBits CShort Source # 
Bits CShort Source # 
Storable CShort Source # 

newtype CUShort Source #

Haskell type representing the C unsigned short type.

Constructors

CUShort Word16 

Instances

Bounded CUShort Source # 
Enum CUShort Source # 
Eq CUShort Source # 

Methods

(==) :: CUShort -> CUShort -> Bool #

(/=) :: CUShort -> CUShort -> Bool #

Integral CUShort Source # 
Num CUShort Source # 
Ord CUShort Source # 
Read CUShort Source # 
Real CUShort Source # 
Show CUShort Source # 
FiniteBits CUShort Source # 
Bits CUShort Source # 
Storable CUShort Source # 

newtype CInt Source #

Haskell type representing the C int type.

Constructors

CInt Int32 

Instances

Bounded CInt Source # 
Enum CInt Source # 
Eq CInt Source # 

Methods

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

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

Integral CInt Source # 
Num CInt Source # 
Ord CInt Source # 

Methods

compare :: CInt -> CInt -> Ordering #

(<) :: CInt -> CInt -> Bool #

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

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

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

max :: CInt -> CInt -> CInt #

min :: CInt -> CInt -> CInt #

Read CInt Source # 
Real CInt Source # 
Show CInt Source # 
FiniteBits CInt Source # 
Bits CInt Source # 
Storable CInt Source # 

newtype CUInt Source #

Haskell type representing the C unsigned int type.

Constructors

CUInt Word32 

Instances

Bounded CUInt Source # 
Enum CUInt Source # 
Eq CUInt Source # 

Methods

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

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

Integral CUInt Source # 
Num CUInt Source # 
Ord CUInt Source # 

Methods

compare :: CUInt -> CUInt -> Ordering #

(<) :: CUInt -> CUInt -> Bool #

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

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

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

max :: CUInt -> CUInt -> CUInt #

min :: CUInt -> CUInt -> CUInt #

Read CUInt Source # 
Real CUInt Source # 
Show CUInt Source # 
FiniteBits CUInt Source # 
Bits CUInt Source # 
Storable CUInt Source # 

newtype CLong Source #

Haskell type representing the C long type.

Constructors

CLong Int64 

Instances

Bounded CLong Source # 
Enum CLong Source # 
Eq CLong Source # 

Methods

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

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

Integral CLong Source # 
Num CLong Source # 
Ord CLong Source # 

Methods

compare :: CLong -> CLong -> Ordering #

(<) :: CLong -> CLong -> Bool #

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

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

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

max :: CLong -> CLong -> CLong #

min :: CLong -> CLong -> CLong #

Read CLong Source # 
Real CLong Source # 
Show CLong Source # 
FiniteBits CLong Source # 
Bits CLong Source # 
Storable CLong Source # 

newtype CULong Source #

Haskell type representing the C unsigned long type.

Constructors

CULong Word64 

Instances

Bounded CULong Source # 
Enum CULong Source # 
Eq CULong Source # 

Methods

(==) :: CULong -> CULong -> Bool #

(/=) :: CULong -> CULong -> Bool #

Integral CULong Source # 
Num CULong Source # 
Ord CULong Source # 
Read CULong Source # 
Real CULong Source # 
Show CULong Source # 
FiniteBits CULong Source # 
Bits CULong Source # 
Storable CULong Source # 

newtype CPtrdiff Source #

Haskell type representing the C ptrdiff_t type.

Constructors

CPtrdiff Int64 

Instances

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

newtype CSize Source #

Haskell type representing the C size_t type.

Constructors

CSize Word64 

Instances

Bounded CSize Source # 
Enum CSize Source # 
Eq CSize Source # 

Methods

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

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

Integral CSize Source # 
Num CSize Source # 
Ord CSize Source # 

Methods

compare :: CSize -> CSize -> Ordering #

(<) :: CSize -> CSize -> Bool #

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

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

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

max :: CSize -> CSize -> CSize #

min :: CSize -> CSize -> CSize #

Read CSize Source # 
Real CSize Source # 
Show CSize Source # 
FiniteBits CSize Source # 
Bits CSize Source # 
Storable CSize Source # 

newtype CWchar Source #

Haskell type representing the C wchar_t type.

Constructors

CWchar Int32 

Instances

Bounded CWchar Source # 
Enum CWchar Source # 
Eq CWchar Source # 

Methods

(==) :: CWchar -> CWchar -> Bool #

(/=) :: CWchar -> CWchar -> Bool #

Integral CWchar Source # 
Num CWchar Source # 
Ord CWchar Source # 
Read CWchar Source # 
Real CWchar Source # 
Show CWchar Source # 
FiniteBits CWchar Source # 
Bits CWchar Source # 
Storable CWchar Source # 

newtype CSigAtomic Source #

Haskell type representing the C sig_atomic_t type.

Constructors

CSigAtomic Int32 

Instances

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

newtype CLLong Source #

Haskell type representing the C long long type.

Constructors

CLLong Int64 

Instances

Bounded CLLong Source # 
Enum CLLong Source # 
Eq CLLong Source # 

Methods

(==) :: CLLong -> CLLong -> Bool #

(/=) :: CLLong -> CLLong -> Bool #

Integral CLLong Source # 
Num CLLong Source # 
Ord CLLong Source # 
Read CLLong Source # 
Real CLLong Source # 
Show CLLong Source # 
FiniteBits CLLong Source # 
Bits CLLong Source # 
Storable CLLong Source # 

newtype CULLong Source #

Haskell type representing the C unsigned long long type.

Constructors

CULLong Word64 

Instances

Bounded CULLong Source # 
Enum CULLong Source # 
Eq CULLong Source # 

Methods

(==) :: CULLong -> CULLong -> Bool #

(/=) :: CULLong -> CULLong -> Bool #

Integral CULLong Source # 
Num CULLong Source # 
Ord CULLong Source # 
Read CULLong Source # 
Real CULLong Source # 
Show CULLong Source # 
FiniteBits CULLong Source # 
Bits CULLong Source # 
Storable CULLong Source # 

newtype CIntPtr Source #

Constructors

CIntPtr Int64 

Instances

Bounded CIntPtr Source # 
Enum CIntPtr Source # 
Eq CIntPtr Source # 

Methods

(==) :: CIntPtr -> CIntPtr -> Bool #

(/=) :: CIntPtr -> CIntPtr -> Bool #

Integral CIntPtr Source # 
Num CIntPtr Source # 
Ord CIntPtr Source # 
Read CIntPtr Source # 
Real CIntPtr Source # 
Show CIntPtr Source # 
FiniteBits CIntPtr Source # 
Bits CIntPtr Source # 
Storable CIntPtr Source # 

newtype CUIntPtr Source #

Constructors

CUIntPtr Word64 

Instances

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

newtype CIntMax Source #

Constructors

CIntMax Int64 

Instances

Bounded CIntMax Source # 
Enum CIntMax Source # 
Eq CIntMax Source # 

Methods

(==) :: CIntMax -> CIntMax -> Bool #

(/=) :: CIntMax -> CIntMax -> Bool #

Integral CIntMax Source # 
Num CIntMax Source # 
Ord CIntMax Source # 
Read CIntMax Source # 
Real CIntMax Source # 
Show CIntMax Source # 
FiniteBits CIntMax Source # 
Bits CIntMax Source # 
Storable CIntMax Source # 

newtype CUIntMax Source #

Constructors

CUIntMax Word64 

Instances

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

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 Source # 
Eq CClock Source # 

Methods

(==) :: CClock -> CClock -> Bool #

(/=) :: CClock -> CClock -> Bool #

Num CClock Source # 
Ord CClock Source # 
Read CClock Source # 
Real CClock Source # 
Show CClock Source # 
Storable CClock Source # 

newtype CTime Source #

Haskell type representing the C time_t type.

Constructors

CTime Int64 

Instances

Enum CTime Source # 
Eq CTime Source # 

Methods

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

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

Num CTime Source # 
Ord CTime Source # 

Methods

compare :: CTime -> CTime -> Ordering #

(<) :: CTime -> CTime -> Bool #

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

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

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

max :: CTime -> CTime -> CTime #

min :: CTime -> CTime -> CTime #

Read CTime Source # 
Real CTime Source # 
Show CTime Source # 
Storable CTime Source # 

newtype CUSeconds Source #

Haskell type representing the C useconds_t type.

Since: 4.4.0.0

Constructors

CUSeconds Word32 

Instances

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

newtype CSUSeconds Source #

Haskell type representing the C suseconds_t type.

Since: 4.4.0.0

Constructors

CSUSeconds Int64 

Instances

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

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 Source # 
Eq CFloat Source # 

Methods

(==) :: CFloat -> CFloat -> Bool #

(/=) :: CFloat -> CFloat -> Bool #

Floating CFloat Source # 
Fractional CFloat Source # 
Num CFloat Source # 
Ord CFloat Source # 
Read CFloat Source # 
Real CFloat Source # 
RealFloat CFloat Source # 
RealFrac CFloat Source # 
Show CFloat Source # 
Storable CFloat Source # 

newtype CDouble Source #

Haskell type representing the C double type.

Constructors

CDouble Double 

Instances

Enum CDouble Source # 
Eq CDouble Source # 

Methods

(==) :: CDouble -> CDouble -> Bool #

(/=) :: CDouble -> CDouble -> Bool #

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

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.