Refactor the FPTOOLS_CHECK_HTYPE macro
[ghc-base.git] / include / CTypes.h
index b2d5c3e..3ca9f1c 100644 (file)
@@ -1,48 +1,56 @@
-/* -----------------------------------------------------------------------------
- * $Id: CTypes.h,v 1.1 2001/06/28 14:15:04 simonmar Exp $
- *
- * Dirty CPP hackery for CTypes/CTypesISO
- *
- * (c) The FFI task force, 2000
- * -------------------------------------------------------------------------- */
+{- --------------------------------------------------------------------------
+// Dirty CPP hackery for CTypes/CTypesISO
+//
+// (c) The FFI task force, 2000
+// --------------------------------------------------------------------------
+-}
 
-#include "MachDeps.h"
+#ifndef CTYPES__H
+#define CTYPES__H
 
-/* As long as there is no automatic derivation of classes for newtypes we resort
-   to extremely dirty cpp-hackery.   :-P   Some care has to be taken when the
-   macros below are modified, otherwise the layout rule will bite you. */
+#include "Typeable.h"
 
-/* A hacked version for GHC follows the Haskell 98 version... */
+{-
+// As long as there is no automatic derivation of classes for newtypes we resort
+// to extremely dirty cpp-hackery.   :-P   Some care has to be taken when the
+// macros below are modified, otherwise the layout rule will bite you.
+-}
+
+--  // A hacked version for GHC follows the Haskell 98 version...
 #ifndef __GLASGOW_HASKELL__
 
-#define NUMERIC_TYPE(T,C,S,B) \
+#define ARITHMETIC_TYPE(T,C,S,B) \
 newtype T = T B deriving (Eq, Ord) ; \
 INSTANCE_NUM(T) ; \
-INSTANCE_READ(T) ; \
-INSTANCE_SHOW(T) ; \
+INSTANCE_REAL(T) ; \
+INSTANCE_READ(T,B) ; \
+INSTANCE_SHOW(T,B) ; \
 INSTANCE_ENUM(T) ; \
-INSTANCE_TYPEABLE(T,C,S) ;
+INSTANCE_STORABLE(T) ; \
+INSTANCE_TYPEABLE0(T,C,S) ;
 
 #define INTEGRAL_TYPE(T,C,S,B) \
-NUMERIC_TYPE(T,C,S,B) ; \
+ARITHMETIC_TYPE(T,C,S,B) ; \
 INSTANCE_BOUNDED(T) ; \
-INSTANCE_REAL(T) ; \
 INSTANCE_INTEGRAL(T) ; \
 INSTANCE_BITS(T)
 
 #define FLOATING_TYPE(T,C,S,B) \
-NUMERIC_TYPE(T,C,S,B) ; \
-INSTANCE_REAL(T) ; \
+ARITHMETIC_TYPE(T,C,S,B) ; \
 INSTANCE_FRACTIONAL(T) ; \
 INSTANCE_FLOATING(T) ; \
 INSTANCE_REALFRAC(T) ; \
 INSTANCE_REALFLOAT(T)
 
-#define INSTANCE_READ(T) \
+#ifndef __GLASGOW_HASKELL__
+#define fakeMap map
+#endif
+
+#define INSTANCE_READ(T,B) \
 instance Read T where { \
    readsPrec p s = fakeMap (\(x, t) -> (T x, t)) (readsPrec p s) }
 
-#define INSTANCE_SHOW(T) \
+#define INSTANCE_SHOW(T,B) \
 instance Show T where { \
    showsPrec p (T x) = showsPrec p x }
 
@@ -56,12 +64,6 @@ instance Num T where { \
    signum  (T i) = T (signum i) ; \
    fromInteger x = T (fromInteger x) }
 
-#define INSTANCE_TYPEABLE(T,C,S) \
-C :: TyCon ; \
-C = mkTyCon S ; \
-instance Typeable T where { \
-  typeOf _ = mkAppTy C [] }
-
 #define INSTANCE_BOUNDED(T) \
 instance Bounded T where { \
    minBound = T minBound ; \
@@ -112,7 +114,7 @@ instance Bits T where { \
 instance Fractional T where { \
    (T x) / (T y)  = T (x / y) ; \
    recip   (T x)  = T (recip x) ; \
-   fromRational        r = T (fromRational r) }
+   fromRational r = T (fromRational r) }
 
 #define INSTANCE_FLOATING(T) \
 instance Floating T where { \
@@ -160,176 +162,50 @@ instance RealFloat T where { \
    isIEEE         (T x) = isIEEE x ; \
    (T x) `atan2`  (T y) = T (x `atan2` y) }
 
+#define INSTANCE_STORABLE(T) \
+instance Storable T where { \
+   sizeOf    (T x)       = sizeOf x ; \
+   alignment (T x)       = alignment x ; \
+   peekElemOff a i       = liftM T (peekElemOff (castPtr a) i) ; \
+   pokeElemOff a i (T x) = pokeElemOff (castPtr a) i x }
+
 #else /* __GLASGOW_HASKELL__ */
 
-/* On GHC, we just cast the type of each method to the underlying
- * type.  This means that GHC only needs to generate the dictionary
- * for each instance, rather than a new function for each method (the
- * simplifier currently isn't clever enough to reduce a method that
- * simply deconstructs a newtype and calls the underlying method into
- * an indirection to the underlying method, so that's what we're doing
- * here). 
- */
+--  // GHC can derive any class for a newtype, so we make use of that here...
 
-#define NUMERIC_TYPE(T,C,S,B) \
-newtype T = T B ; \
-INSTANCE_EQ(T,B) ; \
-INSTANCE_ORD(T,B) ; \
-INSTANCE_NUM(T,B) ; \
-INSTANCE_READ(T,B) ; \
-INSTANCE_SHOW(T,B) ; \
-INSTANCE_ENUM(T,B) 
+#define ARITHMETIC_CLASSES  Eq,Ord,Num,Enum,Storable,Real
+#define INTEGRAL_CLASSES Bounded,Integral,Bits
+#define FLOATING_CLASSES Fractional,Floating,RealFrac,RealFloat
+
+#define ARITHMETIC_TYPE(T,C,S,B) \
+newtype T = T B deriving (ARITHMETIC_CLASSES); \
+INSTANCE_READ(T,B); \
+INSTANCE_SHOW(T,B); \
+INSTANCE_TYPEABLE0(T,C,S) ;
 
 #define INTEGRAL_TYPE(T,C,S,B) \
-NUMERIC_TYPE(T,C,S,B) ;  \
-INSTANCE_BOUNDED(T,B) ; \
-INSTANCE_REAL(T,B) ; \
-INSTANCE_INTEGRAL(T,B) ; \
-INSTANCE_BITS(T,B)
+newtype T = T B deriving (ARITHMETIC_CLASSES, INTEGRAL_CLASSES); \
+INSTANCE_READ(T,B); \
+INSTANCE_SHOW(T,B); \
+INSTANCE_TYPEABLE0(T,C,S) ;
 
 #define FLOATING_TYPE(T,C,S,B) \
-NUMERIC_TYPE(T,C,S,B) ; \
-INSTANCE_REAL(T,B) ; \
-INSTANCE_FRACTIONAL(T,B) ; \
-INSTANCE_FLOATING(T,B) ; \
-INSTANCE_REALFRAC(T) ; \
-INSTANCE_REALFLOAT(T,B)
-
-#define INSTANCE_EQ(T,B) \
-instance Eq T where { \
-   (==)                = unsafeCoerce# ((==) :: B -> B -> Bool); \
-   (/=)                = unsafeCoerce# ((/=) :: B -> B -> Bool); }
-
-#define INSTANCE_ORD(T,B) \
-instance Ord T where { \
-   compare             = unsafeCoerce# (compare :: B -> B -> Ordering); \
-   (<)                 = unsafeCoerce# ((<) :: B -> B -> Bool); \
-   (<=)                        = unsafeCoerce# ((<=) :: B -> B -> Bool); \
-   (>=)                        = unsafeCoerce# ((>=) :: B -> B -> Bool); \
-   (>)                 = unsafeCoerce# ((>) :: B -> B -> Bool); \
-   max                 = unsafeCoerce# (max :: B -> B -> B); \
-   min                 = unsafeCoerce# (min :: B -> B -> B); }
+newtype T = T B deriving (ARITHMETIC_CLASSES, FLOATING_CLASSES); \
+INSTANCE_READ(T,B); \
+INSTANCE_SHOW(T,B); \
+INSTANCE_TYPEABLE0(T,C,S) ;
 
 #define INSTANCE_READ(T,B) \
 instance Read T where { \
-   readsPrec           = unsafeCoerce# (readsPrec :: Int -> ReadS B); \
-   readList            = unsafeCoerce# (readList  :: ReadS [B]); }
+   readsPrec            = unsafeCoerce# (readsPrec :: Int -> ReadS B); \
+   readList             = unsafeCoerce# (readList  :: ReadS [B]); }
 
 #define INSTANCE_SHOW(T,B) \
 instance Show T where { \
-   showsPrec           = unsafeCoerce# (showsPrec :: Int -> B -> ShowS); \
-   show                        = unsafeCoerce# (show :: B -> String); \
-   showList            = unsafeCoerce# (showList :: [B] -> ShowS); }
-
-#define INSTANCE_NUM(T,B) \
-instance Num T where { \
-   (+)                 = unsafeCoerce# ((+) :: B -> B -> B); \
-   (-)                 = unsafeCoerce# ((-) :: B -> B -> B); \
-   (*)                 = unsafeCoerce# ((*) :: B -> B -> B); \
-   negate              = unsafeCoerce# (negate :: B -> B); \
-   abs                 = unsafeCoerce# (abs :: B -> B); \
-   signum              = unsafeCoerce# (signum :: B -> B); \
-   fromInteger         = unsafeCoerce# (fromInteger :: Integer -> B); }
-
-#define INSTANCE_BOUNDED(T,B) \
-instance Bounded T where { \
-   minBound = T minBound ; \
-   maxBound = T maxBound }
-
-#define INSTANCE_ENUM(T,B) \
-instance Enum T where { \
-    succ               = unsafeCoerce# (succ :: B -> B); \
-    pred               = unsafeCoerce# (pred :: B -> B); \
-    toEnum              = unsafeCoerce# (toEnum :: Int -> B); \
-    fromEnum            = unsafeCoerce# (fromEnum :: B -> Int); \
-    enumFrom           = unsafeCoerce# (enumFrom :: B -> [B]); \
-    enumFromThen       = unsafeCoerce# (enumFromThen :: B -> B -> [B]); \
-    enumFromTo         = unsafeCoerce# (enumFromTo :: B -> B -> [B]); \
-    enumFromThenTo     = unsafeCoerce# (enumFromThenTo :: B -> B -> B -> [B]);}
-
-#define INSTANCE_REAL(T,B) \
-instance Real T where { \
-   toRational = unsafeCoerce# (toRational :: B -> Rational) }
-
-#define INSTANCE_INTEGRAL(T,B) \
-instance Integral T where { \
-    quot               = unsafeCoerce# (quot:: B -> B -> B); \
-    rem                        = unsafeCoerce# (rem:: B -> B -> B); \
-    div                        = unsafeCoerce# (div:: B -> B -> B); \
-    mod                        = unsafeCoerce# (mod:: B -> B -> B); \
-    quotRem            = unsafeCoerce# (quotRem:: B -> B -> (B,B)); \
-    divMod             = unsafeCoerce# (divMod:: B -> B -> (B,B)); \
-    toInteger          = unsafeCoerce# (toInteger:: B -> Integer); }
-
-#define INSTANCE_BITS(T,B) \
-instance Bits T where { \
-  (.&.)                        = unsafeCoerce# ((.&.) :: B -> B -> B); \
-  (.|.)                        = unsafeCoerce# ((.|.) :: B -> B -> B); \
-  xor                  = unsafeCoerce# (xor:: B -> B -> B); \
-  complement           = unsafeCoerce# (complement:: B -> B); \
-  shift                = unsafeCoerce# (shift:: B -> Int -> B); \
-  rotate               = unsafeCoerce# (rotate:: B -> Int -> B); \
-  bit                  = unsafeCoerce# (bit:: Int -> B); \
-  setBit               = unsafeCoerce# (setBit:: B -> Int -> B); \
-  clearBit             = unsafeCoerce# (clearBit:: B -> Int -> B); \
-  complementBit        = unsafeCoerce# (complementBit:: B -> Int -> B); \
-  testBit              = unsafeCoerce# (testBit:: B -> Int -> Bool); \
-  bitSize              = unsafeCoerce# (bitSize:: B -> Int); \
-  isSigned             = unsafeCoerce# (isSigned:: B -> Bool); }
-
-#define INSTANCE_FRACTIONAL(T,B) \
-instance Fractional T where { \
-    (/)                        = unsafeCoerce# ((/) :: B -> B -> B); \
-    recip              = unsafeCoerce# (recip :: B -> B); \
-    fromRational       = unsafeCoerce# (fromRational :: Rational -> B); }
-
-#define INSTANCE_FLOATING(T,B) \
-instance Floating T where { \
-    pi                 = unsafeCoerce# (pi :: B); \
-    exp                        = unsafeCoerce# (exp :: B -> B); \
-    log                        = unsafeCoerce# (log :: B -> B); \
-    sqrt               = unsafeCoerce# (sqrt :: B -> B); \
-    (**)               = unsafeCoerce# ((**) :: B -> B -> B); \
-    logBase            = unsafeCoerce# (logBase :: B -> B -> B); \
-    sin                        = unsafeCoerce# (sin :: B -> B); \
-    cos                        = unsafeCoerce# (cos :: B -> B); \
-    tan                        = unsafeCoerce# (tan :: B -> B); \
-    asin               = unsafeCoerce# (asin :: B -> B); \
-    acos               = unsafeCoerce# (acos :: B -> B); \
-    atan               = unsafeCoerce# (atan :: B -> B); \
-    sinh               = unsafeCoerce# (sinh :: B -> B); \
-    cosh               = unsafeCoerce# (cosh :: B -> B); \
-    tanh               = unsafeCoerce# (tanh :: B -> B); \
-    asinh              = unsafeCoerce# (asinh :: B -> B); \
-    acosh              = unsafeCoerce# (acosh :: B -> B); \
-    atanh              = unsafeCoerce# (atanh :: B -> B); }
-
-/* The coerce trick doesn't work for RealFrac, these methods are
- * polymorphic and overloaded.
- */
-#define INSTANCE_REALFRAC(T) \
-instance RealFrac T where { \
-   properFraction (T x) = let (m,y) = properFraction x in (m, T y) ; \
-   truncate (T x) = truncate x ; \
-   round    (T x) = round x ; \
-   ceiling  (T x) = ceiling x ; \
-   floor    (T x) = floor x }
-
-#define INSTANCE_REALFLOAT(T,B) \
-instance RealFloat T where { \
-    floatRadix         = unsafeCoerce# (floatRadix :: B -> Integer); \
-    floatDigits                = unsafeCoerce# (floatDigits :: B -> Int); \
-    floatRange         = unsafeCoerce# (floatRange :: B -> (Int,Int)); \
-    decodeFloat                = unsafeCoerce# (decodeFloat :: B -> (Integer,Int)); \
-    encodeFloat                = unsafeCoerce# (encodeFloat :: Integer -> Int -> B); \
-    exponent           = unsafeCoerce# (exponent :: B -> Int); \
-    significand                = unsafeCoerce# (significand :: B -> B); \
-    scaleFloat         = unsafeCoerce# (scaleFloat :: Int -> B -> B); \
-    isNaN              = unsafeCoerce# (isNaN :: B -> Bool); \
-    isInfinite         = unsafeCoerce# (isInfinite :: B -> Bool); \
-    isDenormalized     = unsafeCoerce# (isDenormalized :: B -> Bool); \
-    isNegativeZero     = unsafeCoerce# (isNegativeZero :: B -> Bool); \
-    isIEEE             = unsafeCoerce# (isIEEE :: B -> Bool); \
-    atan2              = unsafeCoerce# (atan2 :: B -> B -> B); }
+   showsPrec            = unsafeCoerce# (showsPrec :: Int -> B -> ShowS); \
+   show                 = unsafeCoerce# (show :: B -> String); \
+   showList             = unsafeCoerce# (showList :: [B] -> ShowS); }
 
 #endif /* __GLASGOW_HASKELL__ */
+
+#endif