diff options
author | Herbert Valerio Riedel <hvr@gnu.org> | 2013-09-15 23:05:05 +0200 |
---|---|---|
committer | Herbert Valerio Riedel <hvr@gnu.org> | 2013-09-17 09:54:07 +0200 |
commit | 0f5eae0232a86ec57d841a83e6929361e2751270 (patch) | |
tree | 7cc7b87fce8238cd9ff6b65fb0c37f515191aa6e /libraries/base/include | |
parent | 43ece172e7045d5ba633be6193f3e908eaa81f00 (diff) | |
download | haskell-0f5eae0232a86ec57d841a83e6929361e2751270.tar.gz |
Constant-fold `__GLASGOW_HASKELL__` CPP conditionals
Now that HUGS and NHC specific code has been removed, this commit "folds"
the now redundant `#if((n)def)`s containing `__GLASGOW_HASKELL__`. This
renders `base` officially GHC only.
This commit also removes redundant `{-# LANGUAGE CPP #-}`.
Signed-off-by: Herbert Valerio Riedel <hvr@gnu.org>
Diffstat (limited to 'libraries/base/include')
-rw-r--r-- | libraries/base/include/CTypes.h | 160 | ||||
-rw-r--r-- | libraries/base/include/HsBase.h | 4 | ||||
-rw-r--r-- | libraries/base/include/OldTypeable.h | 94 | ||||
-rw-r--r-- | libraries/base/include/Typeable.h | 94 |
4 files changed, 0 insertions, 352 deletions
diff --git a/libraries/base/include/CTypes.h b/libraries/base/include/CTypes.h index 14ec79dcc2..a33d1faab5 100644 --- a/libraries/base/include/CTypes.h +++ b/libraries/base/include/CTypes.h @@ -16,164 +16,6 @@ // 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 ARITHMETIC_TYPE(T,C,S,B) \ -newtype T = T B deriving (Eq, Ord) ; \ -INSTANCE_NUM(T) ; \ -INSTANCE_REAL(T) ; \ -INSTANCE_READ(T,B) ; \ -INSTANCE_SHOW(T,B) ; \ -INSTANCE_ENUM(T) ; \ -INSTANCE_STORABLE(T) ; \ -INSTANCE_TYPEABLE0(T,C,S) ; - -#define INTEGRAL_TYPE(T,C,S,B) \ -ARITHMETIC_TYPE(T,C,S,B) ; \ -INSTANCE_BOUNDED(T) ; \ -INSTANCE_INTEGRAL(T) ; \ -INSTANCE_BITS(T) - -#define FLOATING_TYPE(T,C,S,B) \ -ARITHMETIC_TYPE(T,C,S,B) ; \ -INSTANCE_FRACTIONAL(T) ; \ -INSTANCE_FLOATING(T) ; \ -INSTANCE_REALFRAC(T) ; \ -INSTANCE_REALFLOAT(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,B) \ -instance Show T where { \ - showsPrec p (T x) = showsPrec p x } - -#define INSTANCE_NUM(T) \ -instance Num T where { \ - (T i) + (T j) = T (i + j) ; \ - (T i) - (T j) = T (i - j) ; \ - (T i) * (T j) = T (i * j) ; \ - negate (T i) = T (negate i) ; \ - abs (T i) = T (abs i) ; \ - signum (T i) = T (signum i) ; \ - fromInteger x = T (fromInteger x) } - -#define INSTANCE_BOUNDED(T) \ -instance Bounded T where { \ - minBound = T minBound ; \ - maxBound = T maxBound } - -#define INSTANCE_ENUM(T) \ -instance Enum T where { \ - succ (T i) = T (succ i) ; \ - pred (T i) = T (pred i) ; \ - toEnum x = T (toEnum x) ; \ - fromEnum (T i) = fromEnum i ; \ - enumFrom (T i) = fakeMap T (enumFrom i) ; \ - enumFromThen (T i) (T j) = fakeMap T (enumFromThen i j) ; \ - enumFromTo (T i) (T j) = fakeMap T (enumFromTo i j) ; \ - enumFromThenTo (T i) (T j) (T k) = fakeMap T (enumFromThenTo i j k) } - -#define INSTANCE_REAL(T) \ -instance Real T where { \ - toRational (T i) = toRational i } - -#define INSTANCE_INTEGRAL(T) \ -instance Integral T where { \ - (T i) `quot` (T j) = T (i `quot` j) ; \ - (T i) `rem` (T j) = T (i `rem` j) ; \ - (T i) `div` (T j) = T (i `div` j) ; \ - (T i) `mod` (T j) = T (i `mod` j) ; \ - (T i) `quotRem` (T j) = let (q,r) = i `quotRem` j in (T q, T r) ; \ - (T i) `divMod` (T j) = let (d,m) = i `divMod` j in (T d, T m) ; \ - toInteger (T i) = toInteger i } - -#define INSTANCE_BITS(T) \ -instance Bits T where { \ - (T x) .&. (T y) = T (x .&. y) ; \ - (T x) .|. (T y) = T (x .|. y) ; \ - (T x) `xor` (T y) = T (x `xor` y) ; \ - complement (T x) = T (complement x) ; \ - shift (T x) n = T (shift x n) ; \ - unsafeShiftL (T x) n = T (unsafeShiftL x n) ; \ - unsafeShiftR (T x) n = T (unsafeShiftR x n) ; \ - rotate (T x) n = T (rotate x n) ; \ - bit n = T (bit n) ; \ - setBit (T x) n = T (setBit x n) ; \ - clearBit (T x) n = T (clearBit x n) ; \ - complementBit (T x) n = T (complementBit x n) ; \ - testBit (T x) n = testBit x n ; \ - bitSize (T x) = bitSize x ; \ - isSigned (T x) = isSigned x ; \ - popCount (T x) = popCount x } - -#define INSTANCE_FRACTIONAL(T) \ -instance Fractional T where { \ - (T x) / (T y) = T (x / y) ; \ - recip (T x) = T (recip x) ; \ - fromRational r = T (fromRational r) } - -#define INSTANCE_FLOATING(T) \ -instance Floating T where { \ - pi = pi ; \ - exp (T x) = T (exp x) ; \ - log (T x) = T (log x) ; \ - sqrt (T x) = T (sqrt x) ; \ - (T x) ** (T y) = T (x ** y) ; \ - (T x) `logBase` (T y) = T (x `logBase` y) ; \ - sin (T x) = T (sin x) ; \ - cos (T x) = T (cos x) ; \ - tan (T x) = T (tan x) ; \ - asin (T x) = T (asin x) ; \ - acos (T x) = T (acos x) ; \ - atan (T x) = T (atan x) ; \ - sinh (T x) = T (sinh x) ; \ - cosh (T x) = T (cosh x) ; \ - tanh (T x) = T (tanh x) ; \ - asinh (T x) = T (asinh x) ; \ - acosh (T x) = T (acosh x) ; \ - atanh (T x) = T (atanh x) } - -#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) \ -instance RealFloat T where { \ - floatRadix (T x) = floatRadix x ; \ - floatDigits (T x) = floatDigits x ; \ - floatRange (T x) = floatRange x ; \ - decodeFloat (T x) = decodeFloat x ; \ - encodeFloat m n = T (encodeFloat m n) ; \ - exponent (T x) = exponent x ; \ - significand (T x) = T (significand x) ; \ - scaleFloat n (T x) = T (scaleFloat n x) ; \ - isNaN (T x) = isNaN x ; \ - isInfinite (T x) = isInfinite x ; \ - isDenormalized (T x) = isDenormalized x ; \ - isNegativeZero (T x) = isNegativeZero x ; \ - 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__ */ - -- // GHC can derive any class for a newtype, so we make use of that here... #define ARITHMETIC_CLASSES Eq,Ord,Num,Enum,Storable,Real @@ -215,6 +57,4 @@ instance Show T where { \ show = unsafeCoerce# (show :: B -> String); \ showList = unsafeCoerce# (showList :: [B] -> ShowS); } -#endif /* __GLASGOW_HASKELL__ */ - #endif diff --git a/libraries/base/include/HsBase.h b/libraries/base/include/HsBase.h index b70a7295da..46d0f0c102 100644 --- a/libraries/base/include/HsBase.h +++ b/libraries/base/include/HsBase.h @@ -305,10 +305,6 @@ __hscore_setmode( int fd, HsBool toBin ) #endif } -#if __GLASGOW_HASKELL__ - -#endif /* __GLASGOW_HASKELL__ */ - #if defined(__MINGW32__) // We want the versions of stat/fstat/lseek that use 64-bit offsets, // and you have to ask for those explicitly. Unfortunately there diff --git a/libraries/base/include/OldTypeable.h b/libraries/base/include/OldTypeable.h index 38fe90f220..311edffe29 100644 --- a/libraries/base/include/OldTypeable.h +++ b/libraries/base/include/OldTypeable.h @@ -14,8 +14,6 @@ #ifndef TYPEABLE_H #define TYPEABLE_H -#ifdef __GLASGOW_HASKELL__ - -- // For GHC, we can use DeriveDataTypeable + StandaloneDeriving to -- // generate the instances. @@ -28,96 +26,4 @@ #define INSTANCE_TYPEABLE6(tycon,tcname,str) deriving instance Typeable6 tycon #define INSTANCE_TYPEABLE7(tycon,tcname,str) deriving instance Typeable7 tycon -#else /* !__GLASGOW_HASKELL__ */ - -#define INSTANCE_TYPEABLE0(tycon,tcname,str) \ -tcname :: TyCon; \ -tcname = mkTyCon str; \ -instance Typeable tycon where { typeOf _ = mkTyConApp tcname [] } - -#define INSTANCE_TYPEABLE1(tycon,tcname,str) \ -tcname = mkTyCon str; \ -instance Typeable1 tycon where { typeOf1 _ = mkTyConApp tcname [] }; \ -instance Typeable a => Typeable (tycon a) where { typeOf = typeOfDefault } - -#define INSTANCE_TYPEABLE2(tycon,tcname,str) \ -tcname = mkTyCon str; \ -instance Typeable2 tycon where { typeOf2 _ = mkTyConApp tcname [] }; \ -instance Typeable a => Typeable1 (tycon a) where { \ - typeOf1 = typeOf1Default }; \ -instance (Typeable a, Typeable b) => Typeable (tycon a b) where { \ - typeOf = typeOfDefault } - -#define INSTANCE_TYPEABLE3(tycon,tcname,str) \ -tcname = mkTyCon str; \ -instance Typeable3 tycon where { typeOf3 _ = mkTyConApp tcname [] }; \ -instance Typeable a => Typeable2 (tycon a) where { \ - typeOf2 = typeOf2Default }; \ -instance (Typeable a, Typeable b) => Typeable1 (tycon a b) where { \ - typeOf1 = typeOf1Default }; \ -instance (Typeable a, Typeable b, Typeable c) => Typeable (tycon a b c) where { \ - typeOf = typeOfDefault } - -#define INSTANCE_TYPEABLE4(tycon,tcname,str) \ -tcname = mkTyCon str; \ -instance Typeable4 tycon where { typeOf4 _ = mkTyConApp tcname [] }; \ -instance Typeable a => Typeable3 (tycon a) where { \ - typeOf3 = typeOf3Default }; \ -instance (Typeable a, Typeable b) => Typeable2 (tycon a b) where { \ - typeOf2 = typeOf2Default }; \ -instance (Typeable a, Typeable b, Typeable c) => Typeable1 (tycon a b c) where { \ - typeOf1 = typeOf1Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable (tycon a b c d) where { \ - typeOf = typeOfDefault } - -#define INSTANCE_TYPEABLE5(tycon,tcname,str) \ -tcname = mkTyCon str; \ -instance Typeable5 tycon where { typeOf5 _ = mkTyConApp tcname [] }; \ -instance Typeable a => Typeable4 (tycon a) where { \ - typeOf4 = typeOf4Default }; \ -instance (Typeable a, Typeable b) => Typeable3 (tycon a b) where { \ - typeOf3 = typeOf3Default }; \ -instance (Typeable a, Typeable b, Typeable c) => Typeable2 (tycon a b c) where { \ - typeOf2 = typeOf2Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable1 (tycon a b c d) where { \ - typeOf1 = typeOf1Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Typeable (tycon a b c d e) where { \ - typeOf = typeOfDefault } - -#define INSTANCE_TYPEABLE6(tycon,tcname,str) \ -tcname = mkTyCon str; \ -instance Typeable6 tycon where { typeOf6 _ = mkTyConApp tcname [] }; \ -instance Typeable a => Typeable5 (tycon a) where { \ - typeOf5 = typeOf5Default }; \ -instance (Typeable a, Typeable b) => Typeable4 (tycon a b) where { \ - typeOf4 = typeOf4Default }; \ -instance (Typeable a, Typeable b, Typeable c) => Typeable3 (tycon a b c) where { \ - typeOf3 = typeOf3Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable2 (tycon a b c d) where { \ - typeOf2 = typeOf2Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Typeable1 (tycon a b c d e) where { \ - typeOf1 = typeOf1Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f) => Typeable (tycon a b c d e f) where { \ - typeOf = typeOfDefault } - -#define INSTANCE_TYPEABLE7(tycon,tcname,str) \ -tcname = mkTyCon str; \ -instance Typeable7 tycon where { typeOf7 _ = mkTyConApp tcname [] }; \ -instance Typeable a => Typeable6 (tycon a) where { \ - typeOf6 = typeOf6Default }; \ -instance (Typeable a, Typeable b) => Typeable5 (tycon a b) where { \ - typeOf5 = typeOf5Default }; \ -instance (Typeable a, Typeable b, Typeable c) => Typeable4 (tycon a b c) where { \ - typeOf4 = typeOf4Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable3 (tycon a b c d) where { \ - typeOf3 = typeOf3Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Typeable2 (tycon a b c d e) where { \ - typeOf2 = typeOf2Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f) => Typeable1 (tycon a b c d e f) where { \ - typeOf1 = typeOf1Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f, Typeable g) => Typeable (tycon a b c d e f g) where { \ - typeOf = typeOfDefault } - -#endif /* !__GLASGOW_HASKELL__ */ - #endif diff --git a/libraries/base/include/Typeable.h b/libraries/base/include/Typeable.h index f8ea998ed3..ae04142014 100644 --- a/libraries/base/include/Typeable.h +++ b/libraries/base/include/Typeable.h @@ -14,8 +14,6 @@ #ifndef TYPEABLE_H #define TYPEABLE_H -#ifdef __GLASGOW_HASKELL__ - -- // For GHC, we can use DeriveDataTypeable + StandaloneDeriving to -- // generate the instances. @@ -28,96 +26,4 @@ #define INSTANCE_TYPEABLE6(tycon,tcname,str) deriving instance Typeable tycon #define INSTANCE_TYPEABLE7(tycon,tcname,str) deriving instance Typeable tycon -#else /* !__GLASGOW_HASKELL__ */ - -#define INSTANCE_TYPEABLE0(tycon,tcname,str) \ -tcname :: TyCon; \ -tcname = mkTyCon str; \ -instance Typeable tycon where { typeOf _ = mkTyConApp tcname [] } - -#define INSTANCE_TYPEABLE1(tycon,tcname,str) \ -tcname = mkTyCon str; \ -instance Typeable1 tycon where { typeOf1 _ = mkTyConApp tcname [] }; \ -instance Typeable a => Typeable (tycon a) where { typeOf = typeOfDefault } - -#define INSTANCE_TYPEABLE2(tycon,tcname,str) \ -tcname = mkTyCon str; \ -instance Typeable2 tycon where { typeOf2 _ = mkTyConApp tcname [] }; \ -instance Typeable a => Typeable1 (tycon a) where { \ - typeOf1 = typeOf1Default }; \ -instance (Typeable a, Typeable b) => Typeable (tycon a b) where { \ - typeOf = typeOfDefault } - -#define INSTANCE_TYPEABLE3(tycon,tcname,str) \ -tcname = mkTyCon str; \ -instance Typeable3 tycon where { typeOf3 _ = mkTyConApp tcname [] }; \ -instance Typeable a => Typeable2 (tycon a) where { \ - typeOf2 = typeOf2Default }; \ -instance (Typeable a, Typeable b) => Typeable1 (tycon a b) where { \ - typeOf1 = typeOf1Default }; \ -instance (Typeable a, Typeable b, Typeable c) => Typeable (tycon a b c) where { \ - typeOf = typeOfDefault } - -#define INSTANCE_TYPEABLE4(tycon,tcname,str) \ -tcname = mkTyCon str; \ -instance Typeable4 tycon where { typeOf4 _ = mkTyConApp tcname [] }; \ -instance Typeable a => Typeable3 (tycon a) where { \ - typeOf3 = typeOf3Default }; \ -instance (Typeable a, Typeable b) => Typeable2 (tycon a b) where { \ - typeOf2 = typeOf2Default }; \ -instance (Typeable a, Typeable b, Typeable c) => Typeable1 (tycon a b c) where { \ - typeOf1 = typeOf1Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable (tycon a b c d) where { \ - typeOf = typeOfDefault } - -#define INSTANCE_TYPEABLE5(tycon,tcname,str) \ -tcname = mkTyCon str; \ -instance Typeable5 tycon where { typeOf5 _ = mkTyConApp tcname [] }; \ -instance Typeable a => Typeable4 (tycon a) where { \ - typeOf4 = typeOf4Default }; \ -instance (Typeable a, Typeable b) => Typeable3 (tycon a b) where { \ - typeOf3 = typeOf3Default }; \ -instance (Typeable a, Typeable b, Typeable c) => Typeable2 (tycon a b c) where { \ - typeOf2 = typeOf2Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable1 (tycon a b c d) where { \ - typeOf1 = typeOf1Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Typeable (tycon a b c d e) where { \ - typeOf = typeOfDefault } - -#define INSTANCE_TYPEABLE6(tycon,tcname,str) \ -tcname = mkTyCon str; \ -instance Typeable6 tycon where { typeOf6 _ = mkTyConApp tcname [] }; \ -instance Typeable a => Typeable5 (tycon a) where { \ - typeOf5 = typeOf5Default }; \ -instance (Typeable a, Typeable b) => Typeable4 (tycon a b) where { \ - typeOf4 = typeOf4Default }; \ -instance (Typeable a, Typeable b, Typeable c) => Typeable3 (tycon a b c) where { \ - typeOf3 = typeOf3Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable2 (tycon a b c d) where { \ - typeOf2 = typeOf2Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Typeable1 (tycon a b c d e) where { \ - typeOf1 = typeOf1Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f) => Typeable (tycon a b c d e f) where { \ - typeOf = typeOfDefault } - -#define INSTANCE_TYPEABLE7(tycon,tcname,str) \ -tcname = mkTyCon str; \ -instance Typeable7 tycon where { typeOf7 _ = mkTyConApp tcname [] }; \ -instance Typeable a => Typeable6 (tycon a) where { \ - typeOf6 = typeOf6Default }; \ -instance (Typeable a, Typeable b) => Typeable5 (tycon a b) where { \ - typeOf5 = typeOf5Default }; \ -instance (Typeable a, Typeable b, Typeable c) => Typeable4 (tycon a b c) where { \ - typeOf4 = typeOf4Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable3 (tycon a b c d) where { \ - typeOf3 = typeOf3Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Typeable2 (tycon a b c d e) where { \ - typeOf2 = typeOf2Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f) => Typeable1 (tycon a b c d e f) where { \ - typeOf1 = typeOf1Default }; \ -instance (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f, Typeable g) => Typeable (tycon a b c d e f g) where { \ - typeOf = typeOfDefault } - -#endif /* !__GLASGOW_HASKELL__ */ - #endif |