diff options
-rw-r--r-- | compiler/GHC/Builtin/primops.txt.pp | 3 | ||||
-rw-r--r-- | compiler/GHC/Core/Opt/ConstantFold.hs | 27 | ||||
-rw-r--r-- | compiler/GHC/StgToCmm/Prim.hs | 9 | ||||
-rw-r--r-- | compiler/GHC/Tc/Deriv/Generate.hs | 3 | ||||
-rw-r--r-- | libraries/base/GHC/Float/RealFracMethods.hs | 4 | ||||
-rw-r--r-- | libraries/base/GHC/Int.hs | 4 | ||||
-rw-r--r-- | libraries/base/GHC/Word.hs | 4 |
7 files changed, 9 insertions, 45 deletions
diff --git a/compiler/GHC/Builtin/primops.txt.pp b/compiler/GHC/Builtin/primops.txt.pp index ec729ac450..bf3b879449 100644 --- a/compiler/GHC/Builtin/primops.txt.pp +++ b/compiler/GHC/Builtin/primops.txt.pp @@ -626,7 +626,6 @@ primop Word32LeOp "leWord32#" Compare Word32# -> Word32# -> Int# primop Word32LtOp "ltWord32#" Compare Word32# -> Word32# -> Int# primop Word32NeOp "neWord32#" Compare Word32# -> Word32# -> Int# -#if WORD_SIZE_IN_BITS < 64 ------------------------------------------------------------------------ section "Int64#" {Operations on 64-bit unsigned words. This type is only used @@ -727,8 +726,6 @@ primop Word64LeOp "leWord64#" Compare Word64# -> Word64# -> Int# primop Word64LtOp "ltWord64#" Compare Word64# -> Word64# -> Int# primop Word64NeOp "neWord64#" Compare Word64# -> Word64# -> Int# -#endif - ------------------------------------------------------------------------ section "Int#" {Operations on native-size integers (32+ bits).} diff --git a/compiler/GHC/Core/Opt/ConstantFold.hs b/compiler/GHC/Core/Opt/ConstantFold.hs index 2da7348d66..e4d04c3548 100644 --- a/compiler/GHC/Core/Opt/ConstantFold.hs +++ b/compiler/GHC/Core/Opt/ConstantFold.hs @@ -10,7 +10,6 @@ ToDo: (i1 + i2) only if it results in a valid Float. -} -{-# LANGUAGE CPP #-} {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE LambdaCase #-} @@ -31,8 +30,6 @@ module GHC.Core.Opt.ConstantFold ) where -#include "MachDeps.h" - import GHC.Prelude import GHC.Platform @@ -317,7 +314,6 @@ primOpRules nm = \case Word32SllOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord32 (const shiftL) ] Word32SrlOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord32 $ const $ shiftRightLogical @Word32 ] -#if WORD_SIZE_IN_BITS < 64 -- Int64 operations Int64AddOp -> mkPrimOpRule nm 2 [ binaryLit (int64Op2 (+)) , identity zeroI64 @@ -387,7 +383,6 @@ primOpRules nm = \case , semiInversePrimOp Word64NotOp ] Word64SllOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord64 (const shiftL) ] Word64SrlOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord64 $ const $ shiftRightLogical @Word64 ] -#endif -- Int operations IntAddOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 (+)) @@ -489,9 +484,7 @@ primOpRules nm = \case Int8ToIntOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendIntLit ] Int16ToIntOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendIntLit ] Int32ToIntOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendIntLit ] -#if WORD_SIZE_IN_BITS < 64 Int64ToIntOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendIntLit ] -#endif IntToInt8Op -> mkPrimOpRule nm 1 [ liftLit narrowInt8Lit , semiInversePrimOp Int8ToIntOp , narrowSubsumesAnd IntAndOp IntToInt8Op 8 ] @@ -501,9 +494,7 @@ primOpRules nm = \case IntToInt32Op -> mkPrimOpRule nm 1 [ liftLit narrowInt32Lit , semiInversePrimOp Int32ToIntOp , narrowSubsumesAnd IntAndOp IntToInt32Op 32 ] -#if WORD_SIZE_IN_BITS < 64 IntToInt64Op -> mkPrimOpRule nm 1 [ liftLit narrowInt64Lit ] -#endif Word8ToWordOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendWordLit , extendNarrowPassthrough WordToWord8Op 0xFF @@ -514,9 +505,7 @@ primOpRules nm = \case Word32ToWordOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendWordLit , extendNarrowPassthrough WordToWord32Op 0xFFFFFFFF ] -#if WORD_SIZE_IN_BITS < 64 Word64ToWordOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendWordLit ] -#endif WordToWord8Op -> mkPrimOpRule nm 1 [ liftLit narrowWord8Lit , semiInversePrimOp Word8ToWordOp @@ -527,9 +516,7 @@ primOpRules nm = \case WordToWord32Op -> mkPrimOpRule nm 1 [ liftLit narrowWord32Lit , semiInversePrimOp Word32ToWordOp , narrowSubsumesAnd WordAndOp WordToWord32Op 32 ] -#if WORD_SIZE_IN_BITS < 64 WordToWord64Op -> mkPrimOpRule nm 1 [ liftLit narrowWord64Lit ] -#endif Word8ToInt8Op -> mkPrimOpRule nm 1 [ liftLitPlatform (litNumCoerce LitNumInt8) , semiInversePrimOp Int8ToWord8Op ] @@ -543,12 +530,10 @@ primOpRules nm = \case , semiInversePrimOp Int32ToWord32Op ] Int32ToWord32Op-> mkPrimOpRule nm 1 [ liftLitPlatform (litNumCoerce LitNumWord32) , semiInversePrimOp Word32ToInt32Op ] -#if WORD_SIZE_IN_BITS < 64 Word64ToInt64Op-> mkPrimOpRule nm 1 [ liftLitPlatform (litNumCoerce LitNumInt64) , semiInversePrimOp Int64ToWord64Op ] Int64ToWord64Op-> mkPrimOpRule nm 1 [ liftLitPlatform (litNumCoerce LitNumWord64) , semiInversePrimOp Word64ToInt64Op ] -#endif WordToIntOp -> mkPrimOpRule nm 1 [ liftLitPlatform (litNumCoerce LitNumInt) , semiInversePrimOp IntToWordOp ] @@ -817,13 +802,11 @@ oneI32 = mkLitInt32 1 zeroW32 = mkLitWord32 0 oneW32 = mkLitWord32 1 -#if WORD_SIZE_IN_BITS < 64 zeroI64, oneI64, zeroW64, oneW64 :: Literal zeroI64 = mkLitInt64 0 oneI64 = mkLitInt64 1 zeroW64 = mkLitWord64 0 oneW64 = mkLitWord64 1 -#endif zerof, onef, twof, zerod, oned, twod :: Literal zerof = mkLitFloat 0.0 @@ -890,7 +873,6 @@ int32Op2 op _ (LitNumber LitNumInt32 i1) (LitNumber LitNumInt32 i2) = int32Result (fromInteger i1 `op` fromInteger i2) int32Op2 _ _ _ _ = Nothing -#if WORD_SIZE_IN_BITS < 64 int64Op2 :: (Integral a, Integral b) => (a -> b -> Integer) @@ -898,7 +880,6 @@ int64Op2 int64Op2 op _ (LitNumber LitNumInt64 i1) (LitNumber LitNumInt64 i2) = int64Result (fromInteger i1 `op` fromInteger i2) int64Op2 _ _ _ _ = Nothing -#endif intOp2 :: (Integral a, Integral b) => (a -> b -> Integer) @@ -968,7 +949,6 @@ word32Op2 op _ (LitNumber LitNumWord32 i1) (LitNumber LitNumWord32 i2) = word32Result (fromInteger i1 `op` fromInteger i2) word32Op2 _ _ _ _ = Nothing -#if WORD_SIZE_IN_BITS < 64 word64Op2 :: (Integral a, Integral b) => (a -> b -> Integer) @@ -976,7 +956,6 @@ word64Op2 word64Op2 op _ (LitNumber LitNumWord64 i1) (LitNumber LitNumWord64 i2) = word64Result (fromInteger i1 `op` fromInteger i2) word64Op2 _ _ _ _ = Nothing -#endif wordOp2 :: (Integral a, Integral b) => (a -> b -> Integer) @@ -1218,7 +1197,6 @@ wordCResult platform result = Just (mkPair [Lit lit, Lit c]) (lit, b) = mkLitWordWrapC platform result c = if b then onei platform else zeroi platform -#if WORD_SIZE_IN_BITS < 64 int64Result :: Integer -> Maybe CoreExpr int64Result result = Just (int64Result' result) @@ -1230,7 +1208,6 @@ word64Result result = Just (word64Result' result) word64Result' :: Integer -> CoreExpr word64Result' result = Lit (mkLitWord64Wrap result) -#endif -- | 'ambiant (primop x) = x', but not nececesarily 'primop (ambient x) = x'. @@ -2118,7 +2095,6 @@ builtinBignumRules = , small_passthrough_app "Word# -> Natural -> Double#" naturalNSName naturalToDoubleName (mkPrimOpId WordToDoubleOp) -#if WORD_SIZE_IN_BITS < 64 , small_passthrough_id "Int64# -> Integer -> Int64#" integerFromInt64Name integerToInt64Name , small_passthrough_id "Word64# -> Integer -> Word64#" @@ -2150,7 +2126,6 @@ builtinBignumRules = , small_passthrough_custom "Int64# -> Integer -> Word#" integerFromInt64Name integerToWordName (\x -> Var (mkPrimOpId IntToWordOp) `App` (Var (mkPrimOpId Int64ToIntOp) `App` x)) -#endif -- Bits.bit , bignum_bit "integerBit" integerBitName mkLitInteger @@ -3057,7 +3032,6 @@ word32Ops = NumOps , numLitType = LitNumWord32 } -#if WORD_SIZE_IN_BITS < 64 int64Ops :: NumOps int64Ops = NumOps { numAdd = Int64AddOp @@ -3073,7 +3047,6 @@ word64Ops = NumOps , numMul = Word64MulOp , numLitType = LitNumWord64 } -#endif intOps :: NumOps intOps = NumOps diff --git a/compiler/GHC/StgToCmm/Prim.hs b/compiler/GHC/StgToCmm/Prim.hs index 290ace9f01..e268761cd7 100644 --- a/compiler/GHC/StgToCmm/Prim.hs +++ b/compiler/GHC/StgToCmm/Prim.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE LambdaCase #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} @@ -16,8 +15,6 @@ module GHC.StgToCmm.Prim ( shouldInlinePrimOp ) where -#include "MachDeps.h" - import GHC.Prelude hiding ((<*>)) import GHC.Platform @@ -1100,10 +1097,8 @@ emitPrimOp dflags primop = case primop of Word16ToInt16Op -> \args -> opNop args Int32ToWord32Op -> \args -> opNop args Word32ToInt32Op -> \args -> opNop args -#if WORD_SIZE_IN_BITS < 64 Int64ToWord64Op -> \args -> opNop args Word64ToInt64Op -> \args -> opNop args -#endif IntToWordOp -> \args -> opNop args WordToIntOp -> \args -> opNop args IntToAddrOp -> \args -> opNop args @@ -1356,7 +1351,6 @@ emitPrimOp dflags primop = case primop of Word32LtOp -> \args -> opTranslate args (MO_U_Lt W32) Word32NeOp -> \args -> opTranslate args (MO_Ne W32) -#if WORD_SIZE_IN_BITS < 64 -- Int64# signed ops Int64ToIntOp -> \args -> opTranslate64 args (\w -> MO_SS_Conv w (wordWidth platform)) MO_I64_ToI @@ -1402,7 +1396,6 @@ emitPrimOp dflags primop = case primop of Word64LeOp -> \args -> opTranslate64 args MO_U_Le MO_W64_Le Word64LtOp -> \args -> opTranslate64 args MO_U_Lt MO_W64_Lt Word64NeOp -> \args -> opTranslate64 args MO_Ne MO_x64_Ne -#endif -- Char# ops @@ -1707,7 +1700,6 @@ emitPrimOp dflags primop = case primop of let stmt = mkAssign (CmmLocal res) (CmmMachOp mop args) emit stmt -#if WORD_SIZE_IN_BITS < 64 opTranslate64 :: [CmmExpr] -> (Width -> MachOp) @@ -1717,7 +1709,6 @@ emitPrimOp dflags primop = case primop of case platformWordSize platform of PW4 -> opCallish args callish PW8 -> opTranslate args $ mkMop W64 -#endif -- | Basically a "manual" case, rather than one of the common repetitive forms -- above. The results are a parameter to the returned function so we know the diff --git a/compiler/GHC/Tc/Deriv/Generate.hs b/compiler/GHC/Tc/Deriv/Generate.hs index e9d12f7a79..7ceefbd57a 100644 --- a/compiler/GHC/Tc/Deriv/Generate.hs +++ b/compiler/GHC/Tc/Deriv/Generate.hs @@ -9,7 +9,6 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DataKinds #-} -{-# LANGUAGE CPP #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} @@ -40,8 +39,6 @@ module GHC.Tc.Deriv.Generate ( getPossibleDataCons, tyConInstArgTys ) where -#include "MachDeps.h" - import GHC.Prelude import GHC.Tc.Utils.Monad diff --git a/libraries/base/GHC/Float/RealFracMethods.hs b/libraries/base/GHC/Float/RealFracMethods.hs index 5f971ad126..35a961579b 100644 --- a/libraries/base/GHC/Float/RealFracMethods.hs +++ b/libraries/base/GHC/Float/RealFracMethods.hs @@ -56,11 +56,13 @@ module GHC.Float.RealFracMethods import GHC.Num.Integer -import GHC.Base +import GHC.Base hiding (uncheckedIShiftRA64#, uncheckedIShiftL64#) import GHC.Num () #if WORD_SIZE_IN_BITS < 64 +import GHC.Base (uncheckedIShiftRA64#, uncheckedIShiftL64#) + #define TO64 integerToInt64# #define FROM64 integerFromInt64# #define MINUS64 subInt64# diff --git a/libraries/base/GHC/Int.hs b/libraries/base/GHC/Int.hs index d8ecc7dc4e..4e10e0ca41 100644 --- a/libraries/base/GHC/Int.hs +++ b/libraries/base/GHC/Int.hs @@ -44,9 +44,11 @@ import Data.Maybe #if WORD_SIZE_IN_BITS < 64 import GHC.Prim +import GHC.Base +#else +import GHC.Base hiding (uncheckedIShiftL64#, uncheckedIShiftRA64#) #endif -import GHC.Base import GHC.Enum import GHC.Num import GHC.Real diff --git a/libraries/base/GHC/Word.hs b/libraries/base/GHC/Word.hs index ec231de2b8..dd803c55b4 100644 --- a/libraries/base/GHC/Word.hs +++ b/libraries/base/GHC/Word.hs @@ -50,9 +50,11 @@ import Data.Maybe #if WORD_SIZE_IN_BITS < 64 import GHC.Prim +import GHC.Base +#else +import GHC.Base hiding (uncheckedShiftL64#, uncheckedShiftRL64#) #endif -import GHC.Base import GHC.Bits import GHC.Enum import GHC.Num |