Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
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 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 are represented as newtype
s of
types in Data.Int and Data.Word, and are instances of
Eq
, Ord
, Num
, Read
,
Show
, Enum
, Storable
,
Bounded
, Real
, Integral
and
Bits
.
Haskell type representing the C char
type.
Instances
Bounded CChar | |
Enum CChar | |
Eq CChar | |
Integral CChar | |
Num CChar | |
Ord CChar | |
Read CChar | |
Real CChar | |
Defined in Foreign.C.Types toRational :: CChar -> Rational # | |
Show CChar | |
Storable CChar | |
Bits CChar | |
Defined in Foreign.C.Types (.&.) :: 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 # | |
FiniteBits CChar | |
Defined in Foreign.C.Types finiteBitSize :: CChar -> Int # countLeadingZeros :: CChar -> Int # countTrailingZeros :: CChar -> Int # |
Haskell type representing the C signed char
type.
Instances
Bounded CSChar | |
Enum CSChar | |
Defined in Foreign.C.Types | |
Eq CSChar | |
Integral CSChar | |
Num CSChar | |
Ord CSChar | |
Read CSChar | |
Real CSChar | |
Defined in Foreign.C.Types toRational :: CSChar -> Rational # | |
Show CSChar | |
Storable CSChar | |
Bits CSChar | |
Defined in Foreign.C.Types (.&.) :: 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 # | |
FiniteBits CSChar | |
Defined in Foreign.C.Types finiteBitSize :: CSChar -> Int # countLeadingZeros :: CSChar -> Int # countTrailingZeros :: CSChar -> Int # |
Haskell type representing the C unsigned char
type.
Instances
Bounded CUChar | |
Enum CUChar | |
Defined in Foreign.C.Types | |
Eq CUChar | |
Integral CUChar | |
Num CUChar | |
Ord CUChar | |
Read CUChar | |
Real CUChar | |
Defined in Foreign.C.Types toRational :: CUChar -> Rational # | |
Show CUChar | |
Storable CUChar | |
Bits CUChar | |
Defined in Foreign.C.Types (.&.) :: 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 # | |
FiniteBits CUChar | |
Defined in Foreign.C.Types finiteBitSize :: CUChar -> Int # countLeadingZeros :: CUChar -> Int # countTrailingZeros :: CUChar -> Int # |
Haskell type representing the C short
type.
Instances
Bounded CShort | |
Enum CShort | |
Defined in Foreign.C.Types | |
Eq CShort | |
Integral CShort | |
Num CShort | |
Ord CShort | |
Read CShort | |
Real CShort | |
Defined in Foreign.C.Types toRational :: CShort -> Rational # | |
Show CShort | |
Storable CShort | |
Bits CShort | |
Defined in Foreign.C.Types (.&.) :: 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 # | |
FiniteBits CShort | |
Defined in Foreign.C.Types finiteBitSize :: CShort -> Int # countLeadingZeros :: CShort -> Int # countTrailingZeros :: CShort -> Int # |
Haskell type representing the C unsigned short
type.
Instances
Haskell type representing the C int
type.
Instances
Bounded CInt | |
Enum CInt | |
Eq CInt | |
Integral CInt | |
Num CInt | |
Ord CInt | |
Read CInt | |
Real CInt | |
Defined in Foreign.C.Types toRational :: CInt -> Rational # | |
Show CInt | |
Storable CInt | |
Defined in Foreign.C.Types | |
Bits CInt | |
Defined in Foreign.C.Types (.&.) :: CInt -> CInt -> CInt # (.|.) :: CInt -> CInt -> CInt # complement :: CInt -> CInt # shift :: CInt -> Int -> CInt # rotate :: CInt -> Int -> CInt # setBit :: CInt -> Int -> CInt # clearBit :: CInt -> Int -> CInt # complementBit :: CInt -> Int -> CInt # testBit :: CInt -> Int -> Bool # bitSizeMaybe :: CInt -> Maybe Int # shiftL :: CInt -> Int -> CInt # unsafeShiftL :: CInt -> Int -> CInt # shiftR :: CInt -> Int -> CInt # unsafeShiftR :: CInt -> Int -> CInt # rotateL :: CInt -> Int -> CInt # | |
FiniteBits CInt | |
Defined in Foreign.C.Types |
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 | |
Defined in Foreign.C.Types toRational :: CUInt -> Rational # | |
Show CUInt | |
Storable CUInt | |
Bits CUInt | |
Defined in Foreign.C.Types (.&.) :: 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 # | |
FiniteBits CUInt | |
Defined in Foreign.C.Types finiteBitSize :: CUInt -> Int # countLeadingZeros :: CUInt -> Int # countTrailingZeros :: CUInt -> Int # |
Haskell type representing the C long
type.
Instances
Bounded CLong | |
Enum CLong | |
Eq CLong | |
Integral CLong | |
Num CLong | |
Ord CLong | |
Read CLong | |
Real CLong | |
Defined in Foreign.C.Types toRational :: CLong -> Rational # | |
Show CLong | |
Storable CLong | |
Bits CLong | |
Defined in Foreign.C.Types (.&.) :: 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 # | |
FiniteBits CLong | |
Defined in Foreign.C.Types finiteBitSize :: CLong -> Int # countLeadingZeros :: CLong -> Int # countTrailingZeros :: CLong -> Int # |
Haskell type representing the C unsigned long
type.
Instances
Bounded CULong | |
Enum CULong | |
Defined in Foreign.C.Types | |
Eq CULong | |
Integral CULong | |
Num CULong | |
Ord CULong | |
Read CULong | |
Real CULong | |
Defined in Foreign.C.Types toRational :: CULong -> Rational # | |
Show CULong | |
Storable CULong | |
Bits CULong | |
Defined in Foreign.C.Types (.&.) :: 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 # | |
FiniteBits CULong | |
Defined in Foreign.C.Types finiteBitSize :: CULong -> Int # countLeadingZeros :: CULong -> Int # countTrailingZeros :: CULong -> Int # |
Haskell type representing the C ptrdiff_t
type.
Instances
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 | |
Defined in Foreign.C.Types toRational :: CSize -> Rational # | |
Show CSize | |
Storable CSize | |
Bits CSize | |
Defined in Foreign.C.Types (.&.) :: 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 # | |
FiniteBits CSize | |
Defined in Foreign.C.Types finiteBitSize :: CSize -> Int # countLeadingZeros :: CSize -> Int # countTrailingZeros :: CSize -> Int # |
Haskell type representing the C wchar_t
type.
Instances
Bounded CWchar | |
Enum CWchar | |
Defined in Foreign.C.Types | |
Eq CWchar | |
Integral CWchar | |
Num CWchar | |
Ord CWchar | |
Read CWchar | |
Real CWchar | |
Defined in Foreign.C.Types toRational :: CWchar -> Rational # | |
Show CWchar | |
Storable CWchar | |
Bits CWchar | |
Defined in Foreign.C.Types (.&.) :: 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 # | |
FiniteBits CWchar | |
Defined in Foreign.C.Types finiteBitSize :: CWchar -> Int # countLeadingZeros :: CWchar -> Int # countTrailingZeros :: CWchar -> Int # |
data CSigAtomic #
Haskell type representing the C sig_atomic_t
type.
Instances
Haskell type representing the C long long
type.
Instances
Bounded CLLong | |
Enum CLLong | |
Defined in Foreign.C.Types | |
Eq CLLong | |
Integral CLLong | |
Num CLLong | |
Ord CLLong | |
Read CLLong | |
Real CLLong | |
Defined in Foreign.C.Types toRational :: CLLong -> Rational # | |
Show CLLong | |
Storable CLLong | |
Bits CLLong | |
Defined in Foreign.C.Types (.&.) :: 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 # | |
FiniteBits CLLong | |
Defined in Foreign.C.Types finiteBitSize :: CLLong -> Int # countLeadingZeros :: CLLong -> Int # countTrailingZeros :: CLLong -> Int # |
Haskell type representing the C unsigned long long
type.
Instances
Instances
Instances
Instances
Instances
Numeric types
These types are are represented as newtype
s of basic
foreign types, and are instances of
Eq
, Ord
, Num
, Read
,
Show
, Enum
and Storable
.
Haskell type representing the C clock_t
type.
Instances
Enum CClock | |
Defined in Foreign.C.Types | |
Eq CClock | |
Num CClock | |
Ord CClock | |
Read CClock | |
Real CClock | |
Defined in Foreign.C.Types toRational :: CClock -> Rational # | |
Show CClock | |
Storable CClock | |
Haskell type representing the C time_t
type.
Instances
Enum CTime | |
Eq CTime | |
Num CTime | |
Ord CTime | |
Read CTime | |
Real CTime | |
Defined in Foreign.C.Types toRational :: CTime -> Rational # | |
Show CTime | |
Storable CTime | |
Floating types
These types are are represented as newtype
s of
Float
and Double
, and are instances of
Eq
, Ord
, Num
, Read
,
Show
, Enum
, Storable
,
Real
, Fractional
, Floating
,
RealFrac
and RealFloat
.
Haskell type representing the C float
type.
Instances
Enum CFloat | |
Defined in Foreign.C.Types | |
Eq CFloat | |
Floating CFloat | |
Fractional CFloat | |
Num CFloat | |
Ord CFloat | |
Read CFloat | |
Real CFloat | |
Defined in Foreign.C.Types toRational :: CFloat -> Rational # | |
RealFloat CFloat | |
Defined in Foreign.C.Types 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 | |
Haskell type representing the C double
type.
Instances
Enum CDouble | |
Eq CDouble | |
Floating CDouble | |
Fractional CDouble | |
Num CDouble | |
Ord CDouble | |
Read CDouble | |
Real CDouble | |
Defined in Foreign.C.Types toRational :: CDouble -> Rational # | |
RealFloat CDouble | |
Defined in Foreign.C.Types 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 | |