diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs
index 5eb0da3ea18f4dd814ae3969ae2a0c5e201dcbaa..65289acaa7aee545e44dca94c6c5ad511a8471ef 100644
--- a/libraries/base/GHC/Base.hs
+++ b/libraries/base/GHC/Base.hs
@@ -1656,6 +1656,18 @@ shiftL# :: Word# -> Int# -> Word#
 a `shiftL#` b   | isTrue# (b >=# WORD_SIZE_IN_BITS#) = 0##
                 | otherwise                          = a `uncheckedShiftL#` b
 
+shiftLWord8# :: Word8# -> Int# -> Word8#
+a `shiftLWord8#` b | isTrue# (b >=# 8#) = wordToWord8# 0##
+                   | otherwise          = a `uncheckedShiftLWord8#` b
+
+shiftLWord16# :: Word16# -> Int# -> Word16#
+a `shiftLWord16#` b | isTrue# (b >=# 16#) = wordToWord16# 0##
+                    | otherwise           = a `uncheckedShiftLWord16#` b
+
+shiftLWord32# :: Word32# -> Int# -> Word32#
+a `shiftLWord32#` b | isTrue# (b >=# 32#) = wordToWord32# 0##
+                    | otherwise           = a `uncheckedShiftLWord32#` b
+
 -- | Shift the argument right by the specified number of bits
 -- (which must be non-negative).
 -- The "RL" means "right, logical" (as opposed to RA for arithmetic)
@@ -1664,12 +1676,36 @@ shiftRL# :: Word# -> Int# -> Word#
 a `shiftRL#` b  | isTrue# (b >=# WORD_SIZE_IN_BITS#) = 0##
                 | otherwise                          = a `uncheckedShiftRL#` b
 
+shiftRLWord8# :: Word8# -> Int# -> Word8#
+a `shiftRLWord8#` b | isTrue# (b >=# 8#) = wordToWord8# 0##
+                    | otherwise          = a `uncheckedShiftRLWord8#` b
+
+shiftRLWord16# :: Word16# -> Int# -> Word16#
+a `shiftRLWord16#` b | isTrue# (b >=# 16#) = wordToWord16# 0##
+                     | otherwise           = a `uncheckedShiftRLWord16#` b
+
+shiftRLWord32# :: Word32# -> Int# -> Word32#
+a `shiftRLWord32#` b | isTrue# (b >=# 32#) = wordToWord32# 0##
+                     | otherwise           = a `uncheckedShiftRLWord32#` b
+
 -- | Shift the argument left by the specified number of bits
 -- (which must be non-negative).
 iShiftL# :: Int# -> Int# -> Int#
 a `iShiftL#` b  | isTrue# (b >=# WORD_SIZE_IN_BITS#) = 0#
                 | otherwise                          = a `uncheckedIShiftL#` b
 
+shiftLInt8# :: Int8# -> Int# -> Int8#
+a `shiftLInt8#` b | isTrue# (b >=# 8#) = intToInt8# 0#
+                  | otherwise          = a `uncheckedShiftLInt8#` b
+
+shiftLInt16# :: Int16# -> Int# -> Int16#
+a `shiftLInt16#` b | isTrue# (b >=# 16#) = intToInt16# 0#
+                   | otherwise           = a `uncheckedShiftLInt16#` b
+
+shiftLInt32# :: Int32# -> Int# -> Int32#
+a `shiftLInt32#` b | isTrue# (b >=# 32#) = intToInt32# 0#
+                   | otherwise           = a `uncheckedShiftLInt32#` b
+
 -- | Shift the argument right (signed) by the specified number of bits
 -- (which must be non-negative).
 -- The "RA" means "right, arithmetic" (as opposed to RL for logical)
@@ -1679,6 +1715,24 @@ a `iShiftRA#` b | isTrue# (b >=# WORD_SIZE_IN_BITS#) = if isTrue# (a <# 0#)
                                                           else 0#
                 | otherwise                          = a `uncheckedIShiftRA#` b
 
+shiftRAInt8# :: Int8# -> Int# -> Int8#
+a `shiftRAInt8#` b | isTrue# (b >=# 8#) = if isTrue# (a `ltInt8#` (intToInt8# 0#))
+                                             then intToInt8# (-1#)
+                                             else intToInt8# 0#
+                   | otherwise          = a `uncheckedShiftRAInt8#` b
+
+shiftRAInt16# :: Int16# -> Int# -> Int16#
+a `shiftRAInt16#` b | isTrue# (b >=# 16#) = if isTrue# (a `ltInt16#` (intToInt16# 0#))
+                                               then intToInt16# (-1#)
+                                               else intToInt16# 0#
+                    | otherwise           = a `uncheckedShiftRAInt16#` b
+
+shiftRAInt32# :: Int32# -> Int# -> Int32#
+a `shiftRAInt32#` b | isTrue# (b >=# 32#) = if isTrue# (a `ltInt32#` (intToInt32# 0#))
+                                               then intToInt32# (-1#)
+                                               else intToInt32# 0#
+                    | otherwise           = a `uncheckedShiftRAInt32#` b
+
 -- | Shift the argument right (unsigned) by the specified number of bits
 -- (which must be non-negative).
 -- The "RL" means "right, logical" (as opposed to RA for arithmetic)
@@ -1686,6 +1740,18 @@ iShiftRL# :: Int# -> Int# -> Int#
 a `iShiftRL#` b | isTrue# (b >=# WORD_SIZE_IN_BITS#) = 0#
                 | otherwise                          = a `uncheckedIShiftRL#` b
 
+shiftRLInt8# :: Int8# -> Int# -> Int8#
+a `shiftRLInt8#` b | isTrue# (b >=# 8#) = intToInt8# 0#
+                   | otherwise          = a `uncheckedShiftRLInt8#` b
+
+shiftRLInt16# :: Int16# -> Int# -> Int16#
+a `shiftRLInt16#` b | isTrue# (b >=# 16#) = intToInt16# 0#
+                    | otherwise           = a `uncheckedShiftRLInt16#` b
+
+shiftRLInt32# :: Int32# -> Int# -> Int32#
+a `shiftRLInt32#` b | isTrue# (b >=# 32#) = intToInt32# 0#
+                    | otherwise           = a `uncheckedShiftRLInt32#` b
+
 -- Rules for C strings (the functions themselves are now in GHC.CString)
 {-# RULES
 "unpack"       [~1] forall a   . unpackCString# a             = build (unpackFoldrCString# a)
diff --git a/libraries/base/GHC/Int.hs b/libraries/base/GHC/Int.hs
index 6713130c147e2d7acc7122b1d31b9b30c92d1e54..7e6802c67f0431a620454cd48d67641f55b29b2e 100644
--- a/libraries/base/GHC/Int.hs
+++ b/libraries/base/GHC/Int.hs
@@ -194,29 +194,29 @@ instance Bits Int8 where
     {-# INLINE testBit #-}
     {-# INLINE popCount #-}
 
-    (I8# x#) .&.   (I8# y#)   = I8# (intToInt8# ((int8ToInt# x#) `andI#` (int8ToInt# y#)))
-    (I8# x#) .|.   (I8# y#)   = I8# (intToInt8# ((int8ToInt# x#) `orI#`  (int8ToInt# y#)))
-    (I8# x#) `xor` (I8# y#)   = I8# (intToInt8# ((int8ToInt# x#) `xorI#` (int8ToInt# y#)))
-    complement (I8# x#)       = I8# (intToInt8# (notI# (int8ToInt# x#)))
+    (I8# x#) .&.   (I8# y#)   = I8# (word8ToInt8# (int8ToWord8# x# `andWord8#` int8ToWord8# y#))
+    (I8# x#) .|.   (I8# y#)   = I8# (word8ToInt8# (int8ToWord8# x# `orWord8#`  int8ToWord8# y#))
+    (I8# x#) `xor` (I8# y#)   = I8# (word8ToInt8# (int8ToWord8# x# `xorWord8#` int8ToWord8# y#))
+    complement (I8# x#)       = I8# (word8ToInt8# (notWord8# (int8ToWord8# x#)))
     (I8# x#) `shift` (I# i#)
-        | isTrue# (i# >=# 0#) = I8# (intToInt8# ((int8ToInt# x#) `iShiftL#` i#))
-        | otherwise           = I8# (intToInt8# ((int8ToInt# x#) `iShiftRA#` negateInt# i#))
+        | isTrue# (i# >=# 0#) = I8# (x# `shiftLInt8#` i#)
+        | otherwise           = I8# (x# `shiftRAInt8#` negateInt# i#)
     (I8# x#) `shiftL`       (I# i#)
-        | isTrue# (i# >=# 0#) = I8# (intToInt8# ((int8ToInt# x#) `iShiftL#` i#))
+        | isTrue# (i# >=# 0#) = I8# (x# `shiftLInt8#` i#)
         | otherwise           = overflowError
-    (I8# x#) `unsafeShiftL` (I# i#) = I8# (intToInt8# ((int8ToInt# x#) `uncheckedIShiftL#` i#))
+    (I8# x#) `unsafeShiftL` (I# i#) = I8# (x# `uncheckedShiftLInt8#` i#)
     (I8# x#) `shiftR`       (I# i#)
-        | isTrue# (i# >=# 0#) = I8# (intToInt8# ((int8ToInt# x#) `iShiftRA#` i#))
+        | isTrue# (i# >=# 0#) = I8# (x# `shiftRAInt8#` i#)
         | otherwise           = overflowError
-    (I8# x#) `unsafeShiftR` (I# i#) = I8# (intToInt8# ((int8ToInt# x#) `uncheckedIShiftRA#` i#))
+    (I8# x#) `unsafeShiftR` (I# i#) = I8# (x# `uncheckedShiftRAInt8#` i#)
     (I8# x#) `rotate` (I# i#)
         | isTrue# (i'# ==# 0#)
         = I8# x#
         | otherwise
-        = I8# (intToInt8# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
-                                       (x'# `uncheckedShiftRL#` (8# -# i'#)))))
+        = I8# (word8ToInt8# ((x'# `uncheckedShiftLWord8#` i'#) `orWord8#`
+                             (x'# `uncheckedShiftRLWord8#` (8# -# i'#))))
         where
-        !x'# = narrow8Word# (int2Word# (int8ToInt# x#))
+        !x'# = int8ToWord8# x#
         !i'# = word2Int# (int2Word# i# `and#` 7##)
     bitSizeMaybe i            = Just (finiteBitSize i)
     bitSize i                 = finiteBitSize i
@@ -411,29 +411,29 @@ instance Bits Int16 where
     {-# INLINE testBit #-}
     {-# INLINE popCount #-}
 
-    (I16# x#) .&.   (I16# y#)  = I16# (intToInt16# ((int16ToInt# x#) `andI#` (int16ToInt# y#)))
-    (I16# x#) .|.   (I16# y#)  = I16# (intToInt16# ((int16ToInt# x#) `orI#`  (int16ToInt# y#)))
-    (I16# x#) `xor` (I16# y#)  = I16# (intToInt16# ((int16ToInt# x#) `xorI#` (int16ToInt# y#)))
-    complement (I16# x#)       = I16# (intToInt16# (notI# (int16ToInt# x#)))
+    (I16# x#) .&.   (I16# y#)  = I16# (word16ToInt16# (int16ToWord16# x# `andWord16#` int16ToWord16# y#))
+    (I16# x#) .|.   (I16# y#)  = I16# (word16ToInt16# (int16ToWord16# x# `orWord16#`  int16ToWord16# y#))
+    (I16# x#) `xor` (I16# y#)  = I16# (word16ToInt16# (int16ToWord16# x# `xorWord16#` int16ToWord16# y#))
+    complement (I16# x#)       = I16# (word16ToInt16# (notWord16# (int16ToWord16# x#)))
     (I16# x#) `shift` (I# i#)
-        | isTrue# (i# >=# 0#)  = I16# (intToInt16# ((int16ToInt# x#) `iShiftL#` i#))
-        | otherwise            = I16# (intToInt16# ((int16ToInt# x#) `iShiftRA#` negateInt# i#))
+        | isTrue# (i# >=# 0#)  = I16# (x# `shiftLInt16#` i#)
+        | otherwise            = I16# (x# `shiftRAInt16#` negateInt# i#)
     (I16# x#) `shiftL`       (I# i#)
-        | isTrue# (i# >=# 0#)  = I16# (intToInt16# ((int16ToInt# x#) `iShiftL#` i#))
+        | isTrue# (i# >=# 0#)  = I16# (x# `shiftLInt16#` i#)
         | otherwise            = overflowError
-    (I16# x#) `unsafeShiftL` (I# i#) = I16# (intToInt16# ((int16ToInt# x#) `uncheckedIShiftL#` i#))
+    (I16# x#) `unsafeShiftL` (I# i#) = I16# (x# `uncheckedShiftLInt16#` i#)
     (I16# x#) `shiftR`       (I# i#)
-        | isTrue# (i# >=# 0#)  = I16# (intToInt16# ((int16ToInt# x#) `iShiftRA#` i#))
+        | isTrue# (i# >=# 0#)  = I16# (x# `shiftRAInt16#` i#)
         | otherwise            = overflowError
-    (I16# x#) `unsafeShiftR` (I# i#) = I16# (intToInt16# ((int16ToInt# x#) `uncheckedIShiftRA#` i#))
+    (I16# x#) `unsafeShiftR` (I# i#) = I16# (x# `uncheckedShiftRAInt16#` i#)
     (I16# x#) `rotate` (I# i#)
         | isTrue# (i'# ==# 0#)
         = I16# x#
         | otherwise
-        = I16# (intToInt16# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
-                                         (x'# `uncheckedShiftRL#` (16# -# i'#)))))
+        = I16# (word16ToInt16# ((x'# `uncheckedShiftLWord16#` i'#) `orWord16#`
+                               (x'# `uncheckedShiftRLWord16#` (16# -# i'#))))
         where
-        !x'# = narrow16Word# (int2Word# (int16ToInt# x#))
+        !x'# = int16ToWord16# x#
         !i'# = word2Int# (int2Word# i# `and#` 15##)
     bitSizeMaybe i             = Just (finiteBitSize i)
     bitSize i                  = finiteBitSize i
@@ -627,25 +627,25 @@ instance Bits Int32 where
     (I32# x#) `xor` (I32# y#)  = I32# (intToInt32# ((int32ToInt# x#) `xorI#` (int32ToInt# y#)))
     complement (I32# x#)       = I32# (intToInt32# (notI# (int32ToInt# x#)))
     (I32# x#) `shift` (I# i#)
-        | isTrue# (i# >=# 0#)  = I32# (intToInt32# ((int32ToInt# x#) `iShiftL#` i#))
-        | otherwise            = I32# (intToInt32# ((int32ToInt# x#) `iShiftRA#` negateInt# i#))
+        | isTrue# (i# >=# 0#)  = I32# (x# `shiftLInt32#` i#)
+        | otherwise            = I32# (x# `shiftRAInt32#` negateInt# i#)
     (I32# x#) `shiftL`       (I# i#)
-        | isTrue# (i# >=# 0#)  = I32# (intToInt32# ((int32ToInt# x#) `iShiftL#` i#))
+        | isTrue# (i# >=# 0#)  = I32# (x# `shiftLInt32#` i#)
         | otherwise            = overflowError
     (I32# x#) `unsafeShiftL` (I# i#) =
-        I32# (intToInt32# ((int32ToInt# x#) `uncheckedIShiftL#` i#))
+        I32# (x# `uncheckedShiftLInt32#` i#)
     (I32# x#) `shiftR`       (I# i#)
-        | isTrue# (i# >=# 0#)  = I32# (intToInt32# ((int32ToInt# x#) `iShiftRA#` i#))
+        | isTrue# (i# >=# 0#)  = I32# (x# `shiftRAInt32#` i#)
         | otherwise            = overflowError
-    (I32# x#) `unsafeShiftR` (I# i#) = I32# (intToInt32# ((int32ToInt# x#) `uncheckedIShiftRA#` i#))
+    (I32# x#) `unsafeShiftR` (I# i#) = I32# (x# `uncheckedShiftRAInt32#` i#)
     (I32# x#) `rotate` (I# i#)
         | isTrue# (i'# ==# 0#)
         = I32# x#
         | otherwise
-        = I32# (intToInt32# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
-                                         (x'# `uncheckedShiftRL#` (32# -# i'#)))))
+        = I32# (word32ToInt32# ((x'# `uncheckedShiftLWord32#` i'#) `orWord32#`
+                                (x'# `uncheckedShiftRLWord32#` (32# -# i'#))))
         where
-        !x'# = narrow32Word# (int2Word# (int32ToInt# x#))
+        !x'# = int32ToWord32# x#
         !i'# = word2Int# (int2Word# i# `and#` 31##)
     bitSizeMaybe i             = Just (finiteBitSize i)
     bitSize i                  = finiteBitSize i
diff --git a/libraries/base/GHC/Word.hs b/libraries/base/GHC/Word.hs
index 77d63cc9d7bb06cc1c791ceb0a671a4b6a842156..7a81d0fc19c9f44c9d069d1b9f34c3d8c411f574 100644
--- a/libraries/base/GHC/Word.hs
+++ b/libraries/base/GHC/Word.hs
@@ -180,26 +180,26 @@ instance Bits Word8 where
     {-# INLINE testBit #-}
     {-# INLINE popCount #-}
 
-    (W8# x#) .&.   (W8# y#)   = W8# (wordToWord8# ((word8ToWord# x#) `and#` (word8ToWord# y#)))
-    (W8# x#) .|.   (W8# y#)   = W8# (wordToWord8# ((word8ToWord# x#) `or#`  (word8ToWord# y#)))
-    (W8# x#) `xor` (W8# y#)   = W8# (wordToWord8# ((word8ToWord# x#) `xor#` (word8ToWord# y#)))
-    complement (W8# x#)       = W8# (wordToWord8# (not# (word8ToWord# x#)))
+    (W8# x#) .&.   (W8# y#)   = W8# (x# `andWord8#` y#)
+    (W8# x#) .|.   (W8# y#)   = W8# (x# `orWord8#`  y#)
+    (W8# x#) `xor` (W8# y#)   = W8# (x# `xorWord8#` y#)
+    complement (W8# x#)       = W8# (notWord8# x#)
     (W8# x#) `shift` (I# i#)
-        | isTrue# (i# >=# 0#) = W8# (wordToWord8# ((word8ToWord# x#) `shiftL#` i#))
-        | otherwise           = W8# (wordToWord8# ((word8ToWord# x#) `shiftRL#` negateInt# i#))
+        | isTrue# (i# >=# 0#) = W8# (x# `shiftLWord8#` i#)
+        | otherwise           = W8# (x# `shiftRLWord8#` negateInt# i#)
     (W8# x#) `shiftL`       (I# i#)
-        | isTrue# (i# >=# 0#) = W8# (wordToWord8# ((word8ToWord# x#) `shiftL#` i#))
+        | isTrue# (i# >=# 0#) = W8# (x# `shiftLWord8#` i#)
         | otherwise           = overflowError
     (W8# x#) `unsafeShiftL` (I# i#) =
-        W8# (wordToWord8# ((word8ToWord# x#) `uncheckedShiftL#` i#))
+        W8# (x# `uncheckedShiftLWord8#` i#)
     (W8# x#) `shiftR`       (I# i#)
-        | isTrue# (i# >=# 0#) = W8# (wordToWord8# ((word8ToWord# x#) `shiftRL#` i#))
+        | isTrue# (i# >=# 0#) = W8# (x# `shiftRLWord8#` i#)
         | otherwise           = overflowError
-    (W8# x#) `unsafeShiftR` (I# i#) = W8# (wordToWord8# ((word8ToWord# x#) `uncheckedShiftRL#` i#))
+    (W8# x#) `unsafeShiftR` (I# i#) = W8# (x# `uncheckedShiftRLWord8#` i#)
     (W8# x#) `rotate`       (I# i#)
         | isTrue# (i'# ==# 0#) = W8# x#
-        | otherwise  = W8# (wordToWord8# (((word8ToWord# x#) `uncheckedShiftL#` i'#) `or#`
-                                          ((word8ToWord# x#) `uncheckedShiftRL#` (8# -# i'#))))
+        | otherwise  = W8# ((x# `uncheckedShiftLWord8#` i'#) `orWord8#`
+                            (x# `uncheckedShiftRLWord8#` (8# -# i'#)))
         where
         !i'# = word2Int# (int2Word# i# `and#` 7##)
     bitSizeMaybe i            = Just (finiteBitSize i)
@@ -331,25 +331,24 @@ instance Enum Word16 where
 -- | @since 2.01
 instance Integral Word16 where
     quot    (W16# x#) y@(W16# y#)
-        | y /= 0                    = W16# (wordToWord16# ((word16ToWord# x#) `quotWord#` (word16ToWord# y#)))
+        | y /= 0                    = W16# (x# `quotWord16#` y#)
         | otherwise                 = divZeroError
     rem     (W16# x#) y@(W16# y#)
-        | y /= 0                    = W16# (wordToWord16# ((word16ToWord# x#) `remWord#` (word16ToWord# y#)))
+        | y /= 0                    = W16# (x# `remWord16#` y#)
         | otherwise                 = divZeroError
     div     (W16# x#) y@(W16# y#)
-        | y /= 0                    = W16# (wordToWord16# ((word16ToWord# x#) `quotWord#` (word16ToWord# y#)))
+        | y /= 0                    = W16# (x# `quotWord16#` y#)
         | otherwise                 = divZeroError
     mod     (W16# x#) y@(W16# y#)
-        | y /= 0                    = W16# (wordToWord16# ((word16ToWord# x#) `remWord#` (word16ToWord# y#)))
+        | y /= 0                    = W16# (x# `remWord16#` y#)
         | otherwise                 = divZeroError
     quotRem (W16# x#) y@(W16# y#)
-        | y /= 0                  = case (word16ToWord# x#) `quotRemWord#` (word16ToWord# y#) of
-                                    (# q, r #) ->
-                                        (W16# (wordToWord16# q), W16# (wordToWord16# r))
+        | y /= 0                  = case x# `quotRemWord16#` y# of
+                                    (# q, r #) -> (W16# q, W16# r)
         | otherwise                 = divZeroError
     divMod  (W16# x#) y@(W16# y#)
-        | y /= 0                    = (W16# (wordToWord16# ((word16ToWord# x#) `quotWord#` (word16ToWord# y#)))
-                                      ,W16# (wordToWord16# ((word16ToWord# x#) `remWord#` (word16ToWord# y#))))
+        | y /= 0                    = (W16# (x# `quotWord16#` y#)
+                                      ,W16# (x# `remWord16#` y#))
         | otherwise                 = divZeroError
     toInteger (W16# x#)             = IS (word2Int# (word16ToWord# x#))
 
@@ -371,26 +370,26 @@ instance Bits Word16 where
     {-# INLINE testBit #-}
     {-# INLINE popCount #-}
 
-    (W16# x#) .&.   (W16# y#)  = W16# (wordToWord16# ((word16ToWord# x#) `and#` (word16ToWord# y#)))
-    (W16# x#) .|.   (W16# y#)  = W16# (wordToWord16# ((word16ToWord# x#) `or#`  (word16ToWord# y#)))
-    (W16# x#) `xor` (W16# y#)  = W16# (wordToWord16# ((word16ToWord# x#) `xor#` (word16ToWord# y#)))
-    complement (W16# x#)       = W16# (wordToWord16# (not# (word16ToWord# x#)))
+    (W16# x#) .&.   (W16# y#)  = W16# (x# `andWord16#` y#)
+    (W16# x#) .|.   (W16# y#)  = W16# (x# `orWord16#`  y#)
+    (W16# x#) `xor` (W16# y#)  = W16# (x# `xorWord16#` y#)
+    complement (W16# x#)       = W16# (notWord16# x#)
     (W16# x#) `shift` (I# i#)
-        | isTrue# (i# >=# 0#)  = W16# (wordToWord16# ((word16ToWord# x#) `shiftL#` i#))
-        | otherwise            = W16# (wordToWord16# ((word16ToWord# x#) `shiftRL#` negateInt# i#))
+        | isTrue# (i# >=# 0#)  = W16# (x# `shiftLWord16#` i#)
+        | otherwise            = W16# (x# `shiftRLWord16#` negateInt# i#)
     (W16# x#) `shiftL`       (I# i#)
-        | isTrue# (i# >=# 0#)  = W16# (wordToWord16# ((word16ToWord# x#) `shiftL#` i#))
+        | isTrue# (i# >=# 0#)  = W16# (x# `shiftLWord16#` i#)
         | otherwise            = overflowError
     (W16# x#) `unsafeShiftL` (I# i#) =
-        W16# (wordToWord16# ((word16ToWord# x#) `uncheckedShiftL#` i#))
+        W16# (x# `uncheckedShiftLWord16#` i#)
     (W16# x#) `shiftR`       (I# i#)
-        | isTrue# (i# >=# 0#)  = W16# (wordToWord16# ((word16ToWord# x#) `shiftRL#` i#))
+        | isTrue# (i# >=# 0#)  = W16# (x# `shiftRLWord16#` i#)
         | otherwise            = overflowError
-    (W16# x#) `unsafeShiftR` (I# i#) = W16# (wordToWord16# ((word16ToWord# x#) `uncheckedShiftRL#` i#))
+    (W16# x#) `unsafeShiftR` (I# i#) = W16# (x# `uncheckedShiftRLWord16#` i#)
     (W16# x#) `rotate`       (I# i#)
         | isTrue# (i'# ==# 0#) = W16# x#
-        | otherwise  = W16# (wordToWord16# (((word16ToWord# x#) `uncheckedShiftL#` i'#) `or#`
-                                            ((word16ToWord# x#) `uncheckedShiftRL#` (16# -# i'#))))
+        | otherwise  = W16# ((x# `uncheckedShiftLWord16#` i'#) `orWord16#`
+                             (x# `uncheckedShiftRLWord16#` (16# -# i'#)))
         where
         !i'# = word2Int# (int2Word# i# `and#` 15##)
     bitSizeMaybe i            = Just (finiteBitSize i)
@@ -608,26 +607,26 @@ instance Bits Word32 where
     {-# INLINE testBit #-}
     {-# INLINE popCount #-}
 
-    (W32# x#) .&.   (W32# y#)  = W32# (wordToWord32# ((word32ToWord# x#) `and#` (word32ToWord# y#)))
-    (W32# x#) .|.   (W32# y#)  = W32# (wordToWord32# ((word32ToWord# x#) `or#`  (word32ToWord# y#)))
-    (W32# x#) `xor` (W32# y#)  = W32# (wordToWord32# ((word32ToWord# x#) `xor#` (word32ToWord# y#)))
-    complement (W32# x#)       = W32# (wordToWord32# (not# (word32ToWord# x#)))
+    (W32# x#) .&.   (W32# y#)  = W32# (x# `andWord32#` y#)
+    (W32# x#) .|.   (W32# y#)  = W32# (x# `orWord32#`  y#)
+    (W32# x#) `xor` (W32# y#)  = W32# (x# `xorWord32#` y#)
+    complement (W32# x#)       = W32# (notWord32# x#)
     (W32# x#) `shift` (I# i#)
-        | isTrue# (i# >=# 0#)  = W32# (wordToWord32# ((word32ToWord# x#) `shiftL#` i#))
-        | otherwise            = W32# (wordToWord32# ((word32ToWord# x#) `shiftRL#` negateInt# i#))
+        | isTrue# (i# >=# 0#)  = W32# (x# `shiftLWord32#` i#)
+        | otherwise            = W32# (x# `shiftRLWord32#` negateInt# i#)
     (W32# x#) `shiftL`       (I# i#)
-        | isTrue# (i# >=# 0#)  = W32# (wordToWord32# ((word32ToWord# x#) `shiftL#` i#))
+        | isTrue# (i# >=# 0#)  = W32# (x# `shiftLWord32#` i#)
         | otherwise            = overflowError
     (W32# x#) `unsafeShiftL` (I# i#) =
-        W32# (wordToWord32# ((word32ToWord# x#) `uncheckedShiftL#` i#))
+        W32# (x# `uncheckedShiftLWord32#` i#)
     (W32# x#) `shiftR`       (I# i#)
-        | isTrue# (i# >=# 0#)  = W32# (wordToWord32# ((word32ToWord# x#) `shiftRL#` i#))
+        | isTrue# (i# >=# 0#)  = W32# (x# `shiftRLWord32#` i#)
         | otherwise            = overflowError
-    (W32# x#) `unsafeShiftR` (I# i#) = W32# (wordToWord32# ((word32ToWord# x#) `uncheckedShiftRL#` i#))
+    (W32# x#) `unsafeShiftR` (I# i#) = W32# (x# `uncheckedShiftRLWord32#` i#)
     (W32# x#) `rotate`       (I# i#)
         | isTrue# (i'# ==# 0#) = W32# x#
-        | otherwise   = W32# (wordToWord32# (((word32ToWord# x#) `uncheckedShiftL#` i'#) `or#`
-                                            ((word32ToWord# x#) `uncheckedShiftRL#` (32# -# i'#))))
+        | otherwise   = W32# ((x# `uncheckedShiftLWord32#` i'#) `orWord32#`
+                              (x# `uncheckedShiftRLWord32#` (32# -# i'#)))
         where
         !i'# = word2Int# (int2Word# i# `and#` 31##)
     bitSizeMaybe i            = Just (finiteBitSize i)