small debugging output cleanup
[ghc-hetmet.git] / compiler / codeGen / CgUtils.hs
index 2f69927..804aeab 100644 (file)
@@ -2,7 +2,7 @@
 --
 -- Code generator utilities; mostly monadic
 --
--- (c) The University of Glasgow 2004
+-- (c) The University of Glasgow 2004-2006
 --
 -----------------------------------------------------------------------------
 
@@ -34,33 +34,29 @@ module CgUtils (
 #include "HsVersions.h"
 
 import CgMonad
-import TyCon           ( TyCon, tyConName )
-import Id              ( Id )
-import Constants       ( wORD_SIZE )
-import SMRep           ( CgRep, StgWord, hALF_WORD_SIZE_IN_BITS, ByteOff,
-                         WordOff, idCgRep )
+import TyCon
+import Id
+import Constants
+import SMRep
 import PprCmm          ( {- instances -} )
 import Cmm
 import CLabel
 import CmmUtils
-import MachOp          ( MachRep(..), wordRep, MachOp(..),  MachHint(..),
-                         mo_wordOr, mo_wordAnd, mo_wordNe, mo_wordEq,
-                         mo_wordULt, mo_wordUGt, mo_wordUGe, machRepByteWidth )
-import ForeignCall     ( CCallConv(..) )
-import Literal         ( Literal(..) )
-import CLabel          ( CLabel, mkStringLitLabel )
-import Digraph         ( SCC(..), stronglyConnComp )
-import ListSetOps      ( assocDefault )
-import Util            ( filterOut, sortLe )
-import DynFlags                ( DynFlags(..), HscTarget(..) )
-import Packages                ( HomeModules )
-import FastString      ( LitString, FastString, bytesFS )
+import MachOp
+import ForeignCall
+import Literal
+import Digraph
+import ListSetOps
+import Util
+import DynFlags
+import FastString
+import PackageConfig
 import Outputable
 
-import Char            ( ord )
-import DATA_BITS
-import DATA_WORD       ( Word8 )
-import Maybe           ( isNothing )
+import Data.Char
+import Data.Bits
+import Data.Word
+import Data.Maybe
 
 -------------------------------------------------------------------------
 --
@@ -213,11 +209,11 @@ addToMemE rep ptr n
 --
 -------------------------------------------------------------------------
 
-tagToClosure :: HomeModules -> TyCon -> CmmExpr -> CmmExpr
-tagToClosure hmods tycon tag
+tagToClosure :: PackageId -> TyCon -> CmmExpr -> CmmExpr
+tagToClosure this_pkg tycon tag
   = CmmLoad (cmmOffsetExprW closure_tbl tag) wordRep
   where closure_tbl = CmmLit (CmmLabel lbl)
-       lbl = mkClosureTableLabel hmods (tyConName tycon)
+       lbl = mkClosureTableLabel this_pkg (tyConName tycon)
 
 -------------------------------------------------------------------------
 --
@@ -478,17 +474,19 @@ mk_switch tag_expr branches mb_deflt lo_tag hi_tag via_C
   where
     use_switch          = {- pprTrace "mk_switch" (
                        ppr tag_expr <+> text "n_tags:" <+> int n_tags <+>
+                        text "branches:" <+> ppr (map fst branches) <+>
                        text "n_branches:" <+> int n_branches <+>
-                       text "lo_tag: " <+> int lo_tag <+>
-                       text "hi_tag: " <+> int hi_tag <+>
-                       text "real_lo_tag: " <+> int real_lo_tag <+>
-                       text "real_hi_tag: " <+> int real_hi_tag) $ -}
+                       text "lo_tag:" <+> int lo_tag <+>
+                       text "hi_tag:" <+> int hi_tag <+>
+                       text "real_lo_tag:" <+> int real_lo_tag <+>
+                       text "real_hi_tag:" <+> int real_hi_tag) $ -}
                   ASSERT( n_branches > 1 && n_tags > 1 ) 
-                  n_tags > 2 && (small || dense || via_C)
-                -- a 2-branch switch always turns into an if.
-    small               = n_tags <= 4
+                  n_tags > 2 && (via_C || (dense && big_enough))
+                -- up to 4 branches we use a decision tree, otherwise
+                 -- a switch (== jump table in the NCG).  This seems to be
+                 -- optimal, and corresponds with what gcc does.
+    big_enough          = n_branches > 4
     dense               = n_branches > (n_tags `div` 2)
-    exhaustive   = n_tags == n_branches
     n_branches   = length branches
     
     -- ignore default slots at each end of the range if there's