haskell2020-0.1.0.0: Haskell 2020[draft] Standard Library

Safe HaskellSafe
LanguageHaskell2010

Foreign.C.Types

Contents

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 are represented as newtypes of types in Data.Int and Data.Word, and are instances of Eq, Ord, Num, Read, Show, Enum, Storable, Bounded, Real, Integral and Bits.

data CChar #

Haskell type representing the C char type.

Instances
Bounded CChar 
Instance details

Defined in Foreign.C.Types

Enum CChar 
Instance details

Defined in Foreign.C.Types

Eq CChar 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CChar 
Instance details

Defined in Foreign.C.Types

Num CChar 
Instance details

Defined in Foreign.C.Types

Ord CChar 
Instance details

Defined in Foreign.C.Types

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 
Instance details

Defined in Foreign.C.Types

Real CChar 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CChar -> Rational #

Show CChar 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CChar -> ShowS #

show :: CChar -> String #

showList :: [CChar] -> ShowS #

Storable CChar 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CChar -> Int #

alignment :: CChar -> Int #

peekElemOff :: Ptr CChar -> Int -> IO CChar #

pokeElemOff :: Ptr CChar -> Int -> CChar -> IO () #

peekByteOff :: Ptr b -> Int -> IO CChar #

pokeByteOff :: Ptr b -> Int -> CChar -> IO () #

peek :: Ptr CChar -> IO CChar #

poke :: Ptr CChar -> CChar -> IO () #

Bits CChar 
Instance details

Defined in Foreign.C.Types

FiniteBits CChar 
Instance details

Defined in Foreign.C.Types

data CSChar #

Haskell type representing the C signed char type.

Instances
Bounded CSChar 
Instance details

Defined in Foreign.C.Types

Enum CSChar 
Instance details

Defined in Foreign.C.Types

Eq CSChar 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CSChar 
Instance details

Defined in Foreign.C.Types

Num CSChar 
Instance details

Defined in Foreign.C.Types

Ord CSChar 
Instance details

Defined in Foreign.C.Types

Read CSChar 
Instance details

Defined in Foreign.C.Types

Real CSChar 
Instance details

Defined in Foreign.C.Types

Show CSChar 
Instance details

Defined in Foreign.C.Types

Storable CSChar 
Instance details

Defined in Foreign.C.Types

Bits CSChar 
Instance details

Defined in Foreign.C.Types

FiniteBits CSChar 
Instance details

Defined in Foreign.C.Types

data CUChar #

Haskell type representing the C unsigned char type.

Instances
Bounded CUChar 
Instance details

Defined in Foreign.C.Types

Enum CUChar 
Instance details

Defined in Foreign.C.Types

Eq CUChar 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CUChar 
Instance details

Defined in Foreign.C.Types

Num CUChar 
Instance details

Defined in Foreign.C.Types

Ord CUChar 
Instance details

Defined in Foreign.C.Types

Read CUChar 
Instance details

Defined in Foreign.C.Types

Real CUChar 
Instance details

Defined in Foreign.C.Types

Show CUChar 
Instance details

Defined in Foreign.C.Types

Storable CUChar 
Instance details

Defined in Foreign.C.Types

Bits CUChar 
Instance details

Defined in Foreign.C.Types

FiniteBits CUChar 
Instance details

Defined in Foreign.C.Types

data CShort #

Haskell type representing the C short type.

Instances
Bounded CShort 
Instance details

Defined in Foreign.C.Types

Enum CShort 
Instance details

Defined in Foreign.C.Types

Eq CShort 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CShort 
Instance details

Defined in Foreign.C.Types

Num CShort 
Instance details

Defined in Foreign.C.Types

Ord CShort 
Instance details

Defined in Foreign.C.Types

Read CShort 
Instance details

Defined in Foreign.C.Types

Real CShort 
Instance details

Defined in Foreign.C.Types

Show CShort 
Instance details

Defined in Foreign.C.Types

Storable CShort 
Instance details

Defined in Foreign.C.Types

Bits CShort 
Instance details

Defined in Foreign.C.Types

FiniteBits CShort 
Instance details

Defined in Foreign.C.Types

data CUShort #

Haskell type representing the C unsigned short type.

Instances
Bounded CUShort 
Instance details

Defined in Foreign.C.Types

Enum CUShort 
Instance details

Defined in Foreign.C.Types

Eq CUShort 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CUShort 
Instance details

Defined in Foreign.C.Types

Num CUShort 
Instance details

Defined in Foreign.C.Types

Ord CUShort 
Instance details

Defined in Foreign.C.Types

Read CUShort 
Instance details

Defined in Foreign.C.Types

Real CUShort 
Instance details

Defined in Foreign.C.Types

Show CUShort 
Instance details

Defined in Foreign.C.Types

Storable CUShort 
Instance details

Defined in Foreign.C.Types

Bits CUShort 
Instance details

Defined in Foreign.C.Types

FiniteBits CUShort 
Instance details

Defined in Foreign.C.Types

data CInt #

Haskell type representing the C int type.

Instances
Bounded CInt 
Instance details

Defined in Foreign.C.Types

Enum CInt 
Instance details

Defined in Foreign.C.Types

Methods

succ :: CInt -> CInt #

pred :: CInt -> CInt #

toEnum :: Int -> CInt #

fromEnum :: CInt -> Int #

enumFrom :: CInt -> [CInt] #

enumFromThen :: CInt -> CInt -> [CInt] #

enumFromTo :: CInt -> CInt -> [CInt] #

enumFromThenTo :: CInt -> CInt -> CInt -> [CInt] #

Eq CInt 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CInt 
Instance details

Defined in Foreign.C.Types

Methods

quot :: CInt -> CInt -> CInt #

rem :: CInt -> CInt -> CInt #

div :: CInt -> CInt -> CInt #

mod :: CInt -> CInt -> CInt #

quotRem :: CInt -> CInt -> (CInt, CInt) #

divMod :: CInt -> CInt -> (CInt, CInt) #

toInteger :: CInt -> Integer #

Num CInt 
Instance details

Defined in Foreign.C.Types

Methods

(+) :: CInt -> CInt -> CInt #

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

(*) :: CInt -> CInt -> CInt #

negate :: CInt -> CInt #

abs :: CInt -> CInt #

signum :: CInt -> CInt #

fromInteger :: Integer -> CInt #

Ord CInt 
Instance details

Defined in Foreign.C.Types

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 
Instance details

Defined in Foreign.C.Types

Real CInt 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CInt -> Rational #

Show CInt 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CInt -> ShowS #

show :: CInt -> String #

showList :: [CInt] -> ShowS #

Storable CInt 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CInt -> Int #

alignment :: CInt -> Int #

peekElemOff :: Ptr CInt -> Int -> IO CInt #

pokeElemOff :: Ptr CInt -> Int -> CInt -> IO () #

peekByteOff :: Ptr b -> Int -> IO CInt #

pokeByteOff :: Ptr b -> Int -> CInt -> IO () #

peek :: Ptr CInt -> IO CInt #

poke :: Ptr CInt -> CInt -> IO () #

Bits CInt 
Instance details

Defined in Foreign.C.Types

FiniteBits CInt 
Instance details

Defined in Foreign.C.Types

data CUInt #

Haskell type representing the C unsigned int type.

Instances
Bounded CUInt 
Instance details

Defined in Foreign.C.Types

Enum CUInt 
Instance details

Defined in Foreign.C.Types

Eq CUInt 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CUInt 
Instance details

Defined in Foreign.C.Types

Num CUInt 
Instance details

Defined in Foreign.C.Types

Ord CUInt 
Instance details

Defined in Foreign.C.Types

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 
Instance details

Defined in Foreign.C.Types

Real CUInt 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CUInt -> Rational #

Show CUInt 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CUInt -> ShowS #

show :: CUInt -> String #

showList :: [CUInt] -> ShowS #

Storable CUInt 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CUInt -> Int #

alignment :: CUInt -> Int #

peekElemOff :: Ptr CUInt -> Int -> IO CUInt #

pokeElemOff :: Ptr CUInt -> Int -> CUInt -> IO () #

peekByteOff :: Ptr b -> Int -> IO CUInt #

pokeByteOff :: Ptr b -> Int -> CUInt -> IO () #

peek :: Ptr CUInt -> IO CUInt #

poke :: Ptr CUInt -> CUInt -> IO () #

Bits CUInt 
Instance details

Defined in Foreign.C.Types

FiniteBits CUInt 
Instance details

Defined in Foreign.C.Types

data CLong #

Haskell type representing the C long type.

Instances
Bounded CLong 
Instance details

Defined in Foreign.C.Types

Enum CLong 
Instance details

Defined in Foreign.C.Types

Eq CLong 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CLong 
Instance details

Defined in Foreign.C.Types

Num CLong 
Instance details

Defined in Foreign.C.Types

Ord CLong 
Instance details

Defined in Foreign.C.Types

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 
Instance details

Defined in Foreign.C.Types

Real CLong 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CLong -> Rational #

Show CLong 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CLong -> ShowS #

show :: CLong -> String #

showList :: [CLong] -> ShowS #

Storable CLong 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CLong -> Int #

alignment :: CLong -> Int #

peekElemOff :: Ptr CLong -> Int -> IO CLong #

pokeElemOff :: Ptr CLong -> Int -> CLong -> IO () #

peekByteOff :: Ptr b -> Int -> IO CLong #

pokeByteOff :: Ptr b -> Int -> CLong -> IO () #

peek :: Ptr CLong -> IO CLong #

poke :: Ptr CLong -> CLong -> IO () #

Bits CLong 
Instance details

Defined in Foreign.C.Types

FiniteBits CLong 
Instance details

Defined in Foreign.C.Types

data CULong #

Haskell type representing the C unsigned long type.

Instances
Bounded CULong 
Instance details

Defined in Foreign.C.Types

Enum CULong 
Instance details

Defined in Foreign.C.Types

Eq CULong 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CULong 
Instance details

Defined in Foreign.C.Types

Num CULong 
Instance details

Defined in Foreign.C.Types

Ord CULong 
Instance details

Defined in Foreign.C.Types

Read CULong 
Instance details

Defined in Foreign.C.Types

Real CULong 
Instance details

Defined in Foreign.C.Types

Show CULong 
Instance details

Defined in Foreign.C.Types

Storable CULong 
Instance details

Defined in Foreign.C.Types

Bits CULong 
Instance details

Defined in Foreign.C.Types

FiniteBits CULong 
Instance details

Defined in Foreign.C.Types

data CPtrdiff #

Haskell type representing the C ptrdiff_t type.

Instances
Bounded CPtrdiff 
Instance details

Defined in Foreign.C.Types

Enum CPtrdiff 
Instance details

Defined in Foreign.C.Types

Eq CPtrdiff 
Instance details

Defined in Foreign.C.Types

Integral CPtrdiff 
Instance details

Defined in Foreign.C.Types

Num CPtrdiff 
Instance details

Defined in Foreign.C.Types

Ord CPtrdiff 
Instance details

Defined in Foreign.C.Types

Read CPtrdiff 
Instance details

Defined in Foreign.C.Types

Real CPtrdiff 
Instance details

Defined in Foreign.C.Types

Show CPtrdiff 
Instance details

Defined in Foreign.C.Types

Storable CPtrdiff 
Instance details

Defined in Foreign.C.Types

Bits CPtrdiff 
Instance details

Defined in Foreign.C.Types

FiniteBits CPtrdiff 
Instance details

Defined in Foreign.C.Types

data CSize #

Haskell type representing the C size_t type.

Instances
Bounded CSize 
Instance details

Defined in Foreign.C.Types

Enum CSize 
Instance details

Defined in Foreign.C.Types

Eq CSize 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CSize 
Instance details

Defined in Foreign.C.Types

Num CSize 
Instance details

Defined in Foreign.C.Types

Ord CSize 
Instance details

Defined in Foreign.C.Types

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 
Instance details

Defined in Foreign.C.Types

Real CSize 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CSize -> Rational #

Show CSize 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CSize -> ShowS #

show :: CSize -> String #

showList :: [CSize] -> ShowS #

Storable CSize 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CSize -> Int #

alignment :: CSize -> Int #

peekElemOff :: Ptr CSize -> Int -> IO CSize #

pokeElemOff :: Ptr CSize -> Int -> CSize -> IO () #

peekByteOff :: Ptr b -> Int -> IO CSize #

pokeByteOff :: Ptr b -> Int -> CSize -> IO () #

peek :: Ptr CSize -> IO CSize #

poke :: Ptr CSize -> CSize -> IO () #

Bits CSize 
Instance details

Defined in Foreign.C.Types

FiniteBits CSize 
Instance details

Defined in Foreign.C.Types

data CWchar #

Haskell type representing the C wchar_t type.

Instances
Bounded CWchar 
Instance details

Defined in Foreign.C.Types

Enum CWchar 
Instance details

Defined in Foreign.C.Types

Eq CWchar 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CWchar 
Instance details

Defined in Foreign.C.Types

Num CWchar 
Instance details

Defined in Foreign.C.Types

Ord CWchar 
Instance details

Defined in Foreign.C.Types

Read CWchar 
Instance details

Defined in Foreign.C.Types

Real CWchar 
Instance details

Defined in Foreign.C.Types

Show CWchar 
Instance details

Defined in Foreign.C.Types

Storable CWchar 
Instance details

Defined in Foreign.C.Types

Bits CWchar 
Instance details

Defined in Foreign.C.Types

FiniteBits CWchar 
Instance details

Defined in Foreign.C.Types

data CSigAtomic #

Haskell type representing the C sig_atomic_t type.

Instances
Bounded CSigAtomic 
Instance details

Defined in Foreign.C.Types

Enum CSigAtomic 
Instance details

Defined in Foreign.C.Types

Eq CSigAtomic 
Instance details

Defined in Foreign.C.Types

Integral CSigAtomic 
Instance details

Defined in Foreign.C.Types

Num CSigAtomic 
Instance details

Defined in Foreign.C.Types

Ord CSigAtomic 
Instance details

Defined in Foreign.C.Types

Read CSigAtomic 
Instance details

Defined in Foreign.C.Types

Real CSigAtomic 
Instance details

Defined in Foreign.C.Types

Show CSigAtomic 
Instance details

Defined in Foreign.C.Types

Storable CSigAtomic 
Instance details

Defined in Foreign.C.Types

Bits CSigAtomic 
Instance details

Defined in Foreign.C.Types

FiniteBits CSigAtomic 
Instance details

Defined in Foreign.C.Types

data CLLong #

Haskell type representing the C long long type.

Instances
Bounded CLLong 
Instance details

Defined in Foreign.C.Types

Enum CLLong 
Instance details

Defined in Foreign.C.Types

Eq CLLong 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CLLong 
Instance details

Defined in Foreign.C.Types

Num CLLong 
Instance details

Defined in Foreign.C.Types

Ord CLLong 
Instance details

Defined in Foreign.C.Types

Read CLLong 
Instance details

Defined in Foreign.C.Types

Real CLLong 
Instance details

Defined in Foreign.C.Types

Show CLLong 
Instance details

Defined in Foreign.C.Types

Storable CLLong 
Instance details

Defined in Foreign.C.Types

Bits CLLong 
Instance details

Defined in Foreign.C.Types

FiniteBits CLLong 
Instance details

Defined in Foreign.C.Types

data CULLong #

Haskell type representing the C unsigned long long type.

Instances
Bounded CULLong 
Instance details

Defined in Foreign.C.Types

Enum CULLong 
Instance details

Defined in Foreign.C.Types

Eq CULLong 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CULLong 
Instance details

Defined in Foreign.C.Types

Num CULLong 
Instance details

Defined in Foreign.C.Types

Ord CULLong 
Instance details

Defined in Foreign.C.Types

Read CULLong 
Instance details

Defined in Foreign.C.Types

Real CULLong 
Instance details

Defined in Foreign.C.Types

Show CULLong 
Instance details

Defined in Foreign.C.Types

Storable CULLong 
Instance details

Defined in Foreign.C.Types

Bits CULLong 
Instance details

Defined in Foreign.C.Types

FiniteBits CULLong 
Instance details

Defined in Foreign.C.Types

data CIntPtr #

Instances
Bounded CIntPtr 
Instance details

Defined in Foreign.C.Types

Enum CIntPtr 
Instance details

Defined in Foreign.C.Types

Eq CIntPtr 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CIntPtr 
Instance details

Defined in Foreign.C.Types

Num CIntPtr 
Instance details

Defined in Foreign.C.Types

Ord CIntPtr 
Instance details

Defined in Foreign.C.Types

Read CIntPtr 
Instance details

Defined in Foreign.C.Types

Real CIntPtr 
Instance details

Defined in Foreign.C.Types

Show CIntPtr 
Instance details

Defined in Foreign.C.Types

Storable CIntPtr 
Instance details

Defined in Foreign.C.Types

Bits CIntPtr 
Instance details

Defined in Foreign.C.Types

FiniteBits CIntPtr 
Instance details

Defined in Foreign.C.Types

data CUIntPtr #

Instances
Bounded CUIntPtr 
Instance details

Defined in Foreign.C.Types

Enum CUIntPtr 
Instance details

Defined in Foreign.C.Types

Eq CUIntPtr 
Instance details

Defined in Foreign.C.Types

Integral CUIntPtr 
Instance details

Defined in Foreign.C.Types

Num CUIntPtr 
Instance details

Defined in Foreign.C.Types

Ord CUIntPtr 
Instance details

Defined in Foreign.C.Types

Read CUIntPtr 
Instance details

Defined in Foreign.C.Types

Real CUIntPtr 
Instance details

Defined in Foreign.C.Types

Show CUIntPtr 
Instance details

Defined in Foreign.C.Types

Storable CUIntPtr 
Instance details

Defined in Foreign.C.Types

Bits CUIntPtr 
Instance details

Defined in Foreign.C.Types

FiniteBits CUIntPtr 
Instance details

Defined in Foreign.C.Types

data CIntMax #

Instances
Bounded CIntMax 
Instance details

Defined in Foreign.C.Types

Enum CIntMax 
Instance details

Defined in Foreign.C.Types

Eq CIntMax 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CIntMax 
Instance details

Defined in Foreign.C.Types

Num CIntMax 
Instance details

Defined in Foreign.C.Types

Ord CIntMax 
Instance details

Defined in Foreign.C.Types

Read CIntMax 
Instance details

Defined in Foreign.C.Types

Real CIntMax 
Instance details

Defined in Foreign.C.Types

Show CIntMax 
Instance details

Defined in Foreign.C.Types

Storable CIntMax 
Instance details

Defined in Foreign.C.Types

Bits CIntMax 
Instance details

Defined in Foreign.C.Types

FiniteBits CIntMax 
Instance details

Defined in Foreign.C.Types

data CUIntMax #

Instances
Bounded CUIntMax 
Instance details

Defined in Foreign.C.Types

Enum CUIntMax 
Instance details

Defined in Foreign.C.Types

Eq CUIntMax 
Instance details

Defined in Foreign.C.Types

Integral CUIntMax 
Instance details

Defined in Foreign.C.Types

Num CUIntMax 
Instance details

Defined in Foreign.C.Types

Ord CUIntMax 
Instance details

Defined in Foreign.C.Types

Read CUIntMax 
Instance details

Defined in Foreign.C.Types

Real CUIntMax 
Instance details

Defined in Foreign.C.Types

Show CUIntMax 
Instance details

Defined in Foreign.C.Types

Storable CUIntMax 
Instance details

Defined in Foreign.C.Types

Bits CUIntMax 
Instance details

Defined in Foreign.C.Types

FiniteBits CUIntMax 
Instance details

Defined in Foreign.C.Types

Numeric types

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

data CClock #

Haskell type representing the C clock_t type.

Instances
Enum CClock 
Instance details

Defined in Foreign.C.Types

Eq CClock 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Num CClock 
Instance details

Defined in Foreign.C.Types

Ord CClock 
Instance details

Defined in Foreign.C.Types

Read CClock 
Instance details

Defined in Foreign.C.Types

Real CClock 
Instance details

Defined in Foreign.C.Types

Show CClock 
Instance details

Defined in Foreign.C.Types

Storable CClock 
Instance details

Defined in Foreign.C.Types

data CTime #

Haskell type representing the C time_t type.

Instances
Enum CTime 
Instance details

Defined in Foreign.C.Types

Eq CTime 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Num CTime 
Instance details

Defined in Foreign.C.Types

Ord CTime 
Instance details

Defined in Foreign.C.Types

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 
Instance details

Defined in Foreign.C.Types

Real CTime 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CTime -> Rational #

Show CTime 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CTime -> ShowS #

show :: CTime -> String #

showList :: [CTime] -> ShowS #

Storable CTime 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CTime -> Int #

alignment :: CTime -> Int #

peekElemOff :: Ptr CTime -> Int -> IO CTime #

pokeElemOff :: Ptr CTime -> Int -> CTime -> IO () #

peekByteOff :: Ptr b -> Int -> IO CTime #

pokeByteOff :: Ptr b -> Int -> CTime -> IO () #

peek :: Ptr CTime -> IO CTime #

poke :: Ptr CTime -> CTime -> IO () #

Floating types

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

data CFloat #

Haskell type representing the C float type.

Instances
Enum CFloat 
Instance details

Defined in Foreign.C.Types

Eq CFloat 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Floating CFloat 
Instance details

Defined in Foreign.C.Types

Fractional CFloat 
Instance details

Defined in Foreign.C.Types

Num CFloat 
Instance details

Defined in Foreign.C.Types

Ord CFloat 
Instance details

Defined in Foreign.C.Types

Read CFloat 
Instance details

Defined in Foreign.C.Types

Real CFloat 
Instance details

Defined in Foreign.C.Types

RealFloat CFloat 
Instance details

Defined in Foreign.C.Types

RealFrac CFloat 
Instance details

Defined in Foreign.C.Types

Methods

properFraction :: Integral b => CFloat -> (b, CFloat) #

truncate :: Integral b => CFloat -> b #

round :: Integral b => CFloat -> b #

ceiling :: Integral b => CFloat -> b #

floor :: Integral b => CFloat -> b #

Show CFloat 
Instance details

Defined in Foreign.C.Types

Storable CFloat 
Instance details

Defined in Foreign.C.Types

data CDouble #

Haskell type representing the C double type.

Instances
Enum CDouble 
Instance details

Defined in Foreign.C.Types

Eq CDouble 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Floating CDouble 
Instance details

Defined in Foreign.C.Types

Fractional CDouble 
Instance details

Defined in Foreign.C.Types

Num CDouble 
Instance details

Defined in Foreign.C.Types

Ord CDouble 
Instance details

Defined in Foreign.C.Types

Read CDouble 
Instance details

Defined in Foreign.C.Types

Real CDouble 
Instance details

Defined in Foreign.C.Types

RealFloat CDouble 
Instance details

Defined in Foreign.C.Types

RealFrac CDouble 
Instance details

Defined in Foreign.C.Types

Methods

properFraction :: Integral b => CDouble -> (b, CDouble) #

truncate :: Integral b => CDouble -> b #

round :: Integral b => CDouble -> b #

ceiling :: Integral b => CDouble -> b #

floor :: Integral b => CDouble -> b #

Show CDouble 
Instance details

Defined in Foreign.C.Types

Storable CDouble 
Instance details

Defined in Foreign.C.Types

Other types

data CFile #

Haskell type representing the C FILE type.

data CFpos #

Haskell type representing the C fpos_t type.

data CJmpBuf #

Haskell type representing the C jmp_buf type.