remove a bogus assertion
[ghc-hetmet.git] / compiler / nativeGen / MachRegs.lhs
index 2205ce0..0174fac 100644 (file)
@@ -104,9 +104,9 @@ import Unique
 import UniqSet
 import Constants
 import FastTypes
-import UniqFM
-
-import GHC.Exts
+import FastBool
+import qualified UniqFM as S
+import LazyUniqFM
 
 #if powerpc_TARGET_ARCH
 import Data.Word       ( Word8, Word16, Word32 )
@@ -503,49 +503,49 @@ worst n classN classC
 -- Compare MachRegs.freeRegs  and MachRegs.h to get these numbers.
 --
 #if i386_TARGET_ARCH
-#define ALLOCATABLE_REGS_INTEGER 3#
-#define ALLOCATABLE_REGS_DOUBLE  6#
+#define ALLOCATABLE_REGS_INTEGER (_ILIT(3))
+#define ALLOCATABLE_REGS_DOUBLE  (_ILIT(6))
 #endif
 
 #if x86_64_TARGET_ARCH
-#define ALLOCATABLE_REGS_INTEGER 5#
-#define ALLOCATABLE_REGS_DOUBLE  2#
+#define ALLOCATABLE_REGS_INTEGER (_ILIT(5))
+#define ALLOCATABLE_REGS_DOUBLE  (_ILIT(2))
 #endif
 
 #if powerpc_TARGET_ARCH
-#define ALLOCATABLE_REGS_INTEGER 16#
-#define ALLOCATABLE_REGS_DOUBLE  26#
+#define ALLOCATABLE_REGS_INTEGER (_ILIT(16))
+#define ALLOCATABLE_REGS_DOUBLE  (_ILIT(26))
 #endif
 
 {-# INLINE regClass      #-}
 trivColorable :: RegClass -> UniqSet Reg -> UniqSet Reg -> Bool
-trivColorable classN conflicts exclusions
+trivColorable classN (MkUniqFM conflicts) (MkUniqFM exclusions)
  = {-# SCC "trivColorable" #-}
    let
        {-# INLINE   isSqueesed    #-}
        isSqueesed cI cF ufm
          = case ufm of
-               NodeUFM _ _ left right
+               S.NodeUFM _ _ left right
                 -> case isSqueesed cI cF right of
                        (# s, cI', cF' #)
                         -> case s of
                                False   -> isSqueesed cI' cF' left
                                True    -> (# True, cI', cF' #)
 
-               LeafUFM _ reg
+               S.LeafUFM _ (Lazy reg)
                 -> case regClass reg of
                        RcInteger
-                        -> case cI +# 1# of
+                        -> case cI +# _ILIT(1) of
                                cI' -> (# cI' >=# ALLOCATABLE_REGS_INTEGER, cI', cF #)
 
                        RcDouble
-                        -> case cF +# 1# of
+                        -> case cF +# _ILIT(1) of
                                cF' -> (# cF' >=# ALLOCATABLE_REGS_DOUBLE,  cI, cF' #)
 
-               EmptyUFM
+               S.EmptyUFM
                 ->     (# False, cI, cF #)
 
-   in case isSqueesed 0# 0# conflicts of
+   in case isSqueesed (_ILIT(0)) (_ILIT(0)) conflicts of
        (# False, cI', cF' #)
         -> case isSqueesed cI' cF' exclusions of
                (# s, _, _ #)   -> not s