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 | Trustworthy |
Language | Haskell2010 |
Foreign.C.Types
Description
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 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
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 ofCT
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 forCT
has a valid representation in C.
will yield the same value assizeOf
(undefined
:: CT)sizeof (t)
in C.
matches the alignment constraint enforced by the C implementation foralignment
(undefined
:: CT)t
.- The members
peek
andpoke
of theStorable
class map all values ofCT
to the corresponding value oft
and vice versa. - When an instance of
Bounded
is defined forCT
, the values ofminBound
andmaxBound
coincide witht_MIN
andt_MAX
in C. - When an instance of
Eq
orOrd
is defined forCT
, the predicates defined by the type class implement the same relation as the corresponding predicate in C ont
. - When an instance of
Num
,Read
,Integral
,Fractional
,Floating
,RealFrac
, orRealFloat
is defined forCT
, the arithmetic operations defined by the type class implement the same function as the corresponding arithmetic operations (if available) in C ont
. - When an instance of
Bits
is defined forCT
, the bitwise operation defined by the type class implement the same function as the corresponding bitwise operation in C ont
.
Integral types
These types are represented as newtype
s 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
Haskell type representing the C char
type.
Instances
Bounded CChar | |
Enum CChar | |
Eq CChar | |
Integral CChar | |
Num CChar | |
Ord CChar | |
Read CChar | |
Real CChar | |
Methods toRational :: CChar -> Rational | |
Show CChar | |
FiniteBits CChar | |
Methods finiteBitSize :: CChar -> Int countLeadingZeros :: CChar -> Int countTrailingZeros :: CChar -> Int | |
Bits CChar | |
Methods (.&.) :: CChar -> CChar -> CChar (.|.) :: CChar -> CChar -> CChar xor :: CChar -> CChar -> CChar complement :: CChar -> CChar shift :: CChar -> Int -> CChar rotate :: CChar -> Int -> CChar setBit :: CChar -> Int -> CChar clearBit :: CChar -> Int -> CChar complementBit :: CChar -> Int -> CChar testBit :: CChar -> Int -> Bool bitSizeMaybe :: CChar -> Maybe Int shiftL :: CChar -> Int -> CChar unsafeShiftL :: CChar -> Int -> CChar shiftR :: CChar -> Int -> CChar unsafeShiftR :: CChar -> Int -> CChar rotateL :: CChar -> Int -> CChar | |
Storable CChar | |
newtype CSChar
Haskell type representing the C signed char
type.
Instances
Bounded CSChar | |
Enum CSChar | |
Eq CSChar | |
Integral CSChar | |
Num CSChar | |
Ord CSChar | |
Read CSChar | |
Real CSChar | |
Methods toRational :: CSChar -> Rational | |
Show CSChar | |
FiniteBits CSChar | |
Methods finiteBitSize :: CSChar -> Int countLeadingZeros :: CSChar -> Int countTrailingZeros :: CSChar -> Int | |
Bits CSChar | |
Methods (.&.) :: CSChar -> CSChar -> CSChar (.|.) :: CSChar -> CSChar -> CSChar xor :: CSChar -> CSChar -> CSChar complement :: CSChar -> CSChar shift :: CSChar -> Int -> CSChar rotate :: CSChar -> Int -> CSChar setBit :: CSChar -> Int -> CSChar clearBit :: CSChar -> Int -> CSChar complementBit :: CSChar -> Int -> CSChar testBit :: CSChar -> Int -> Bool bitSizeMaybe :: CSChar -> Maybe Int shiftL :: CSChar -> Int -> CSChar unsafeShiftL :: CSChar -> Int -> CSChar shiftR :: CSChar -> Int -> CSChar unsafeShiftR :: CSChar -> Int -> CSChar rotateL :: CSChar -> Int -> CSChar | |
Storable CSChar | |
newtype CUChar
Haskell type representing the C unsigned char
type.
Instances
Bounded CUChar | |
Enum CUChar | |
Eq CUChar | |
Integral CUChar | |
Num CUChar | |
Ord CUChar | |
Read CUChar | |
Real CUChar | |
Methods toRational :: CUChar -> Rational | |
Show CUChar | |
FiniteBits CUChar | |
Methods finiteBitSize :: CUChar -> Int countLeadingZeros :: CUChar -> Int countTrailingZeros :: CUChar -> Int | |
Bits CUChar | |
Methods (.&.) :: CUChar -> CUChar -> CUChar (.|.) :: CUChar -> CUChar -> CUChar xor :: CUChar -> CUChar -> CUChar complement :: CUChar -> CUChar shift :: CUChar -> Int -> CUChar rotate :: CUChar -> Int -> CUChar setBit :: CUChar -> Int -> CUChar clearBit :: CUChar -> Int -> CUChar complementBit :: CUChar -> Int -> CUChar testBit :: CUChar -> Int -> Bool bitSizeMaybe :: CUChar -> Maybe Int shiftL :: CUChar -> Int -> CUChar unsafeShiftL :: CUChar -> Int -> CUChar shiftR :: CUChar -> Int -> CUChar unsafeShiftR :: CUChar -> Int -> CUChar rotateL :: CUChar -> Int -> CUChar | |
Storable CUChar | |
newtype CShort
Haskell type representing the C short
type.
Instances
Bounded CShort | |
Enum CShort | |
Eq CShort | |
Integral CShort | |
Num CShort | |
Ord CShort | |
Read CShort | |
Real CShort | |
Methods toRational :: CShort -> Rational | |
Show CShort | |
FiniteBits CShort | |
Methods finiteBitSize :: CShort -> Int countLeadingZeros :: CShort -> Int countTrailingZeros :: CShort -> Int | |
Bits CShort | |
Methods (.&.) :: CShort -> CShort -> CShort (.|.) :: CShort -> CShort -> CShort xor :: CShort -> CShort -> CShort complement :: CShort -> CShort shift :: CShort -> Int -> CShort rotate :: CShort -> Int -> CShort setBit :: CShort -> Int -> CShort clearBit :: CShort -> Int -> CShort complementBit :: CShort -> Int -> CShort testBit :: CShort -> Int -> Bool bitSizeMaybe :: CShort -> Maybe Int shiftL :: CShort -> Int -> CShort unsafeShiftL :: CShort -> Int -> CShort shiftR :: CShort -> Int -> CShort unsafeShiftR :: CShort -> Int -> CShort rotateL :: CShort -> Int -> CShort | |
Storable CShort | |
newtype CUShort
Haskell type representing the C unsigned short
type.
Instances
Bounded CUShort | |
Enum CUShort | |
Eq CUShort | |
Integral CUShort | |
Num CUShort | |
Ord CUShort | |
Read CUShort | |
Real CUShort | |
Methods toRational :: CUShort -> Rational | |
Show CUShort | |
FiniteBits CUShort | |
Methods finiteBitSize :: CUShort -> Int countLeadingZeros :: CUShort -> Int countTrailingZeros :: CUShort -> Int | |
Bits CUShort | |
Methods (.&.) :: CUShort -> CUShort -> CUShort (.|.) :: CUShort -> CUShort -> CUShort xor :: CUShort -> CUShort -> CUShort complement :: CUShort -> CUShort shift :: CUShort -> Int -> CUShort rotate :: CUShort -> Int -> CUShort setBit :: CUShort -> Int -> CUShort clearBit :: CUShort -> Int -> CUShort complementBit :: CUShort -> Int -> CUShort testBit :: CUShort -> Int -> Bool bitSizeMaybe :: CUShort -> Maybe Int shiftL :: CUShort -> Int -> CUShort unsafeShiftL :: CUShort -> Int -> CUShort shiftR :: CUShort -> Int -> CUShort unsafeShiftR :: CUShort -> Int -> CUShort rotateL :: CUShort -> Int -> CUShort | |
Storable CUShort | |
newtype CInt
Haskell type representing the C int
type.
Instances
Bounded CInt | |
Enum CInt | |
Eq CInt | |
Integral CInt | |
Num CInt | |
Ord CInt | |
Read CInt | |
Real CInt | |
Methods toRational :: CInt -> Rational | |
Show CInt | |
FiniteBits CInt | |
Methods finiteBitSize :: CInt -> Int countLeadingZeros :: CInt -> Int countTrailingZeros :: CInt -> Int | |
Bits CInt | |
Storable CInt | |
newtype CUInt
Haskell type representing the C unsigned int
type.
Instances
Bounded CUInt | |
Enum CUInt | |
Eq CUInt | |
Integral CUInt | |
Num CUInt | |
Ord CUInt | |
Read CUInt | |
Real CUInt | |
Methods toRational :: CUInt -> Rational | |
Show CUInt | |
FiniteBits CUInt | |
Methods finiteBitSize :: CUInt -> Int countLeadingZeros :: CUInt -> Int countTrailingZeros :: CUInt -> Int | |
Bits CUInt | |
Methods (.&.) :: CUInt -> CUInt -> CUInt (.|.) :: CUInt -> CUInt -> CUInt xor :: CUInt -> CUInt -> CUInt complement :: CUInt -> CUInt shift :: CUInt -> Int -> CUInt rotate :: CUInt -> Int -> CUInt setBit :: CUInt -> Int -> CUInt clearBit :: CUInt -> Int -> CUInt complementBit :: CUInt -> Int -> CUInt testBit :: CUInt -> Int -> Bool bitSizeMaybe :: CUInt -> Maybe Int shiftL :: CUInt -> Int -> CUInt unsafeShiftL :: CUInt -> Int -> CUInt shiftR :: CUInt -> Int -> CUInt unsafeShiftR :: CUInt -> Int -> CUInt rotateL :: CUInt -> Int -> CUInt | |
Storable CUInt | |
newtype CLong
Haskell type representing the C long
type.
Instances
Bounded CLong | |
Enum CLong | |
Eq CLong | |
Integral CLong | |
Num CLong | |
Ord CLong | |
Read CLong | |
Real CLong | |
Methods toRational :: CLong -> Rational | |
Show CLong | |
FiniteBits CLong | |
Methods finiteBitSize :: CLong -> Int countLeadingZeros :: CLong -> Int countTrailingZeros :: CLong -> Int | |
Bits CLong | |
Methods (.&.) :: CLong -> CLong -> CLong (.|.) :: CLong -> CLong -> CLong xor :: CLong -> CLong -> CLong complement :: CLong -> CLong shift :: CLong -> Int -> CLong rotate :: CLong -> Int -> CLong setBit :: CLong -> Int -> CLong clearBit :: CLong -> Int -> CLong complementBit :: CLong -> Int -> CLong testBit :: CLong -> Int -> Bool bitSizeMaybe :: CLong -> Maybe Int shiftL :: CLong -> Int -> CLong unsafeShiftL :: CLong -> Int -> CLong shiftR :: CLong -> Int -> CLong unsafeShiftR :: CLong -> Int -> CLong rotateL :: CLong -> Int -> CLong | |
Storable CLong | |
newtype CULong
Haskell type representing the C unsigned long
type.
Instances
Bounded CULong | |
Enum CULong | |
Eq CULong | |
Integral CULong | |
Num CULong | |
Ord CULong | |
Read CULong | |
Real CULong | |
Methods toRational :: CULong -> Rational | |
Show CULong | |
FiniteBits CULong | |
Methods finiteBitSize :: CULong -> Int countLeadingZeros :: CULong -> Int countTrailingZeros :: CULong -> Int | |
Bits CULong | |
Methods (.&.) :: CULong -> CULong -> CULong (.|.) :: CULong -> CULong -> CULong xor :: CULong -> CULong -> CULong complement :: CULong -> CULong shift :: CULong -> Int -> CULong rotate :: CULong -> Int -> CULong setBit :: CULong -> Int -> CULong clearBit :: CULong -> Int -> CULong complementBit :: CULong -> Int -> CULong testBit :: CULong -> Int -> Bool bitSizeMaybe :: CULong -> Maybe Int shiftL :: CULong -> Int -> CULong unsafeShiftL :: CULong -> Int -> CULong shiftR :: CULong -> Int -> CULong unsafeShiftR :: CULong -> Int -> CULong rotateL :: CULong -> Int -> CULong | |
Storable CULong | |
newtype CPtrdiff
Haskell type representing the C ptrdiff_t
type.
Instances
Bounded CPtrdiff | |
Enum CPtrdiff | |
Eq CPtrdiff | |
Integral CPtrdiff | |
Num CPtrdiff | |
Ord CPtrdiff | |
Read CPtrdiff | |
Real CPtrdiff | |
Methods toRational :: CPtrdiff -> Rational | |
Show CPtrdiff | |
FiniteBits CPtrdiff | |
Methods finiteBitSize :: CPtrdiff -> Int countLeadingZeros :: CPtrdiff -> Int countTrailingZeros :: CPtrdiff -> Int | |
Bits CPtrdiff | |
Methods (.&.) :: CPtrdiff -> CPtrdiff -> CPtrdiff (.|.) :: CPtrdiff -> CPtrdiff -> CPtrdiff xor :: CPtrdiff -> CPtrdiff -> CPtrdiff complement :: CPtrdiff -> CPtrdiff shift :: CPtrdiff -> Int -> CPtrdiff rotate :: CPtrdiff -> Int -> CPtrdiff setBit :: CPtrdiff -> Int -> CPtrdiff clearBit :: CPtrdiff -> Int -> CPtrdiff complementBit :: CPtrdiff -> Int -> CPtrdiff testBit :: CPtrdiff -> Int -> Bool bitSizeMaybe :: CPtrdiff -> Maybe Int shiftL :: CPtrdiff -> Int -> CPtrdiff unsafeShiftL :: CPtrdiff -> Int -> CPtrdiff shiftR :: CPtrdiff -> Int -> CPtrdiff unsafeShiftR :: CPtrdiff -> Int -> CPtrdiff rotateL :: CPtrdiff -> Int -> CPtrdiff | |
Storable CPtrdiff | |
newtype CSize
Haskell type representing the C size_t
type.
Instances
Bounded CSize | |
Enum CSize | |
Eq CSize | |
Integral CSize | |
Num CSize | |
Ord CSize | |
Read CSize | |
Real CSize | |
Methods toRational :: CSize -> Rational | |
Show CSize | |
FiniteBits CSize | |
Methods finiteBitSize :: CSize -> Int countLeadingZeros :: CSize -> Int countTrailingZeros :: CSize -> Int | |
Bits CSize | |
Methods (.&.) :: CSize -> CSize -> CSize (.|.) :: CSize -> CSize -> CSize xor :: CSize -> CSize -> CSize complement :: CSize -> CSize shift :: CSize -> Int -> CSize rotate :: CSize -> Int -> CSize setBit :: CSize -> Int -> CSize clearBit :: CSize -> Int -> CSize complementBit :: CSize -> Int -> CSize testBit :: CSize -> Int -> Bool bitSizeMaybe :: CSize -> Maybe Int shiftL :: CSize -> Int -> CSize unsafeShiftL :: CSize -> Int -> CSize shiftR :: CSize -> Int -> CSize unsafeShiftR :: CSize -> Int -> CSize rotateL :: CSize -> Int -> CSize | |
Storable CSize | |
newtype CWchar
Haskell type representing the C wchar_t
type.
Instances
Bounded CWchar | |
Enum CWchar | |
Eq CWchar | |
Integral CWchar | |
Num CWchar | |
Ord CWchar | |
Read CWchar | |
Real CWchar | |
Methods toRational :: CWchar -> Rational | |
Show CWchar | |
FiniteBits CWchar | |
Methods finiteBitSize :: CWchar -> Int countLeadingZeros :: CWchar -> Int countTrailingZeros :: CWchar -> Int | |
Bits CWchar | |
Methods (.&.) :: CWchar -> CWchar -> CWchar (.|.) :: CWchar -> CWchar -> CWchar xor :: CWchar -> CWchar -> CWchar complement :: CWchar -> CWchar shift :: CWchar -> Int -> CWchar rotate :: CWchar -> Int -> CWchar setBit :: CWchar -> Int -> CWchar clearBit :: CWchar -> Int -> CWchar complementBit :: CWchar -> Int -> CWchar testBit :: CWchar -> Int -> Bool bitSizeMaybe :: CWchar -> Maybe Int shiftL :: CWchar -> Int -> CWchar unsafeShiftL :: CWchar -> Int -> CWchar shiftR :: CWchar -> Int -> CWchar unsafeShiftR :: CWchar -> Int -> CWchar rotateL :: CWchar -> Int -> CWchar | |
Storable CWchar | |
newtype CSigAtomic
Haskell type representing the C sig_atomic_t
type.
Constructors
CSigAtomic Int32 |
Instances
newtype CLLong
Haskell type representing the C long long
type.
Instances
Bounded CLLong | |
Enum CLLong | |
Eq CLLong | |
Integral CLLong | |
Num CLLong | |
Ord CLLong | |
Read CLLong | |
Real CLLong | |
Methods toRational :: CLLong -> Rational | |
Show CLLong | |
FiniteBits CLLong | |
Methods finiteBitSize :: CLLong -> Int countLeadingZeros :: CLLong -> Int countTrailingZeros :: CLLong -> Int | |
Bits CLLong | |
Methods (.&.) :: CLLong -> CLLong -> CLLong (.|.) :: CLLong -> CLLong -> CLLong xor :: CLLong -> CLLong -> CLLong complement :: CLLong -> CLLong shift :: CLLong -> Int -> CLLong rotate :: CLLong -> Int -> CLLong setBit :: CLLong -> Int -> CLLong clearBit :: CLLong -> Int -> CLLong complementBit :: CLLong -> Int -> CLLong testBit :: CLLong -> Int -> Bool bitSizeMaybe :: CLLong -> Maybe Int shiftL :: CLLong -> Int -> CLLong unsafeShiftL :: CLLong -> Int -> CLLong shiftR :: CLLong -> Int -> CLLong unsafeShiftR :: CLLong -> Int -> CLLong rotateL :: CLLong -> Int -> CLLong | |
Storable CLLong | |
newtype CULLong
Haskell type representing the C unsigned long long
type.
Instances
Bounded CULLong | |
Enum CULLong | |
Eq CULLong | |
Integral CULLong | |
Num CULLong | |
Ord CULLong | |
Read CULLong | |
Real CULLong | |
Methods toRational :: CULLong -> Rational | |
Show CULLong | |
FiniteBits CULLong | |
Methods finiteBitSize :: CULLong -> Int countLeadingZeros :: CULLong -> Int countTrailingZeros :: CULLong -> Int | |
Bits CULLong | |
Methods (.&.) :: CULLong -> CULLong -> CULLong (.|.) :: CULLong -> CULLong -> CULLong xor :: CULLong -> CULLong -> CULLong complement :: CULLong -> CULLong shift :: CULLong -> Int -> CULLong rotate :: CULLong -> Int -> CULLong setBit :: CULLong -> Int -> CULLong clearBit :: CULLong -> Int -> CULLong complementBit :: CULLong -> Int -> CULLong testBit :: CULLong -> Int -> Bool bitSizeMaybe :: CULLong -> Maybe Int shiftL :: CULLong -> Int -> CULLong unsafeShiftL :: CULLong -> Int -> CULLong shiftR :: CULLong -> Int -> CULLong unsafeShiftR :: CULLong -> Int -> CULLong rotateL :: CULLong -> Int -> CULLong | |
Storable CULLong | |
newtype CIntPtr
Instances
Bounded CIntPtr | |
Enum CIntPtr | |
Eq CIntPtr | |
Integral CIntPtr | |
Num CIntPtr | |
Ord CIntPtr | |
Read CIntPtr | |
Real CIntPtr | |
Methods toRational :: CIntPtr -> Rational | |
Show CIntPtr | |
FiniteBits CIntPtr | |
Methods finiteBitSize :: CIntPtr -> Int countLeadingZeros :: CIntPtr -> Int countTrailingZeros :: CIntPtr -> Int | |
Bits CIntPtr | |
Methods (.&.) :: CIntPtr -> CIntPtr -> CIntPtr (.|.) :: CIntPtr -> CIntPtr -> CIntPtr xor :: CIntPtr -> CIntPtr -> CIntPtr complement :: CIntPtr -> CIntPtr shift :: CIntPtr -> Int -> CIntPtr rotate :: CIntPtr -> Int -> CIntPtr setBit :: CIntPtr -> Int -> CIntPtr clearBit :: CIntPtr -> Int -> CIntPtr complementBit :: CIntPtr -> Int -> CIntPtr testBit :: CIntPtr -> Int -> Bool bitSizeMaybe :: CIntPtr -> Maybe Int shiftL :: CIntPtr -> Int -> CIntPtr unsafeShiftL :: CIntPtr -> Int -> CIntPtr shiftR :: CIntPtr -> Int -> CIntPtr unsafeShiftR :: CIntPtr -> Int -> CIntPtr rotateL :: CIntPtr -> Int -> CIntPtr | |
Storable CIntPtr | |
newtype CUIntPtr
Instances
Bounded CUIntPtr | |
Enum CUIntPtr | |
Eq CUIntPtr | |
Integral CUIntPtr | |
Num CUIntPtr | |
Ord CUIntPtr | |
Read CUIntPtr | |
Real CUIntPtr | |
Methods toRational :: CUIntPtr -> Rational | |
Show CUIntPtr | |
FiniteBits CUIntPtr | |
Methods finiteBitSize :: CUIntPtr -> Int countLeadingZeros :: CUIntPtr -> Int countTrailingZeros :: CUIntPtr -> Int | |
Bits CUIntPtr | |
Methods (.&.) :: CUIntPtr -> CUIntPtr -> CUIntPtr (.|.) :: CUIntPtr -> CUIntPtr -> CUIntPtr xor :: CUIntPtr -> CUIntPtr -> CUIntPtr complement :: CUIntPtr -> CUIntPtr shift :: CUIntPtr -> Int -> CUIntPtr rotate :: CUIntPtr -> Int -> CUIntPtr setBit :: CUIntPtr -> Int -> CUIntPtr clearBit :: CUIntPtr -> Int -> CUIntPtr complementBit :: CUIntPtr -> Int -> CUIntPtr testBit :: CUIntPtr -> Int -> Bool bitSizeMaybe :: CUIntPtr -> Maybe Int shiftL :: CUIntPtr -> Int -> CUIntPtr unsafeShiftL :: CUIntPtr -> Int -> CUIntPtr shiftR :: CUIntPtr -> Int -> CUIntPtr unsafeShiftR :: CUIntPtr -> Int -> CUIntPtr rotateL :: CUIntPtr -> Int -> CUIntPtr | |
Storable CUIntPtr | |
newtype CIntMax
Instances
Bounded CIntMax | |
Enum CIntMax | |
Eq CIntMax | |
Integral CIntMax | |
Num CIntMax | |
Ord CIntMax | |
Read CIntMax | |
Real CIntMax | |
Methods toRational :: CIntMax -> Rational | |
Show CIntMax | |
FiniteBits CIntMax | |
Methods finiteBitSize :: CIntMax -> Int countLeadingZeros :: CIntMax -> Int countTrailingZeros :: CIntMax -> Int | |
Bits CIntMax | |
Methods (.&.) :: CIntMax -> CIntMax -> CIntMax (.|.) :: CIntMax -> CIntMax -> CIntMax xor :: CIntMax -> CIntMax -> CIntMax complement :: CIntMax -> CIntMax shift :: CIntMax -> Int -> CIntMax rotate :: CIntMax -> Int -> CIntMax setBit :: CIntMax -> Int -> CIntMax clearBit :: CIntMax -> Int -> CIntMax complementBit :: CIntMax -> Int -> CIntMax testBit :: CIntMax -> Int -> Bool bitSizeMaybe :: CIntMax -> Maybe Int shiftL :: CIntMax -> Int -> CIntMax unsafeShiftL :: CIntMax -> Int -> CIntMax shiftR :: CIntMax -> Int -> CIntMax unsafeShiftR :: CIntMax -> Int -> CIntMax rotateL :: CIntMax -> Int -> CIntMax | |
Storable CIntMax | |
newtype CUIntMax
Instances
Bounded CUIntMax | |
Enum CUIntMax | |
Eq CUIntMax | |
Integral CUIntMax | |
Num CUIntMax | |
Ord CUIntMax | |
Read CUIntMax | |
Real CUIntMax | |
Methods toRational :: CUIntMax -> Rational | |
Show CUIntMax | |
FiniteBits CUIntMax | |
Methods finiteBitSize :: CUIntMax -> Int countLeadingZeros :: CUIntMax -> Int countTrailingZeros :: CUIntMax -> Int | |
Bits CUIntMax | |
Methods (.&.) :: CUIntMax -> CUIntMax -> CUIntMax (.|.) :: CUIntMax -> CUIntMax -> CUIntMax xor :: CUIntMax -> CUIntMax -> CUIntMax complement :: CUIntMax -> CUIntMax shift :: CUIntMax -> Int -> CUIntMax rotate :: CUIntMax -> Int -> CUIntMax setBit :: CUIntMax -> Int -> CUIntMax clearBit :: CUIntMax -> Int -> CUIntMax complementBit :: CUIntMax -> Int -> CUIntMax testBit :: CUIntMax -> Int -> Bool bitSizeMaybe :: CUIntMax -> Maybe Int shiftL :: CUIntMax -> Int -> CUIntMax unsafeShiftL :: CUIntMax -> Int -> CUIntMax shiftR :: CUIntMax -> Int -> CUIntMax unsafeShiftR :: CUIntMax -> Int -> CUIntMax rotateL :: CUIntMax -> Int -> CUIntMax | |
Storable CUIntMax | |
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
.
newtype CClock
Haskell type representing the C clock_t
type.
Instances
Enum CClock | |
Eq CClock | |
Num CClock | |
Ord CClock | |
Read CClock | |
Real CClock | |
Methods toRational :: CClock -> Rational | |
Show CClock | |
Storable CClock | |
newtype CTime
Haskell type representing the C time_t
type.
newtype CUSeconds
Haskell type representing the C useconds_t
type.
Since: 4.4.0.0
Instances
Enum CUSeconds | |
Eq CUSeconds | |
Num CUSeconds | |
Ord CUSeconds | |
Read CUSeconds | |
Real CUSeconds | |
Methods toRational :: CUSeconds -> Rational | |
Show CUSeconds | |
Storable CUSeconds | |
newtype CSUSeconds
Haskell type representing the C suseconds_t
type.
Since: 4.4.0.0
Constructors
CSUSeconds Int64 |
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
.
newtype CFloat
Haskell type representing the C float
type.
Instances
Enum CFloat | |
Eq CFloat | |
Floating CFloat | |
Fractional CFloat | |
Num CFloat | |
Ord CFloat | |
Read CFloat | |
Real CFloat | |
Methods toRational :: CFloat -> Rational | |
RealFloat CFloat | |
Methods floatRadix :: CFloat -> Integer floatDigits :: CFloat -> Int floatRange :: CFloat -> (Int, Int) decodeFloat :: CFloat -> (Integer, Int) encodeFloat :: Integer -> Int -> CFloat significand :: CFloat -> CFloat scaleFloat :: Int -> CFloat -> CFloat isInfinite :: CFloat -> Bool isDenormalized :: CFloat -> Bool isNegativeZero :: CFloat -> Bool | |
RealFrac CFloat | |
Show CFloat | |
Storable CFloat | |
newtype CDouble
Haskell type representing the C double
type.
Instances
Enum CDouble | |
Eq CDouble | |
Floating CDouble | |
Fractional CDouble | |
Num CDouble | |
Ord CDouble | |
Read CDouble | |
Real CDouble | |
Methods toRational :: CDouble -> Rational | |
RealFloat CDouble | |
Methods floatRadix :: CDouble -> Integer floatDigits :: CDouble -> Int floatRange :: CDouble -> (Int, Int) decodeFloat :: CDouble -> (Integer, Int) encodeFloat :: Integer -> Int -> CDouble significand :: CDouble -> CDouble scaleFloat :: Int -> CDouble -> CDouble isInfinite :: CDouble -> Bool isDenormalized :: CDouble -> Bool isNegativeZero :: CDouble -> Bool | |
RealFrac CDouble | |
Show CDouble | |
Storable CDouble | |
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.