Adding tracing support
[ghc-hetmet.git] / compiler / deSugar / Desugar.lhs
index 1f9ebe8..dd2ed6d 100644 (file)
@@ -1,48 +1,50 @@
 %
+% (c) The University of Glasgow 2006
 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
 %
-\section[Desugar]{@deSugar@: the main function}
+
+The Desugarer: turning HsSyn into Core.
 
 \begin{code}
 module Desugar ( deSugar, deSugarExpr ) where
 
 #include "HsVersions.h"
 
-import DynFlags                ( DynFlag(..), DynFlags(..), dopt, GhcMode(..) )
-import StaticFlags     ( opt_SccProfilingOn )
-import DriverPhases    ( isHsBoot )
-import HscTypes                ( ModGuts(..), HscEnv(..), 
-                         Dependencies(..), ForeignStubs(..), TypeEnv, IsBootInterface )
-import HsSyn           ( RuleDecl(..), RuleBndr(..), LHsExpr, LRuleDecl )
-import TcRnTypes       ( TcGblEnv(..), ImportAvails(..) )
-import MkIface         ( mkUsageInfo )
-import Id              ( Id, setIdExported, idName )
-import Name            ( Name, isExternalName, nameIsLocalOrFrom, nameOccName )
+import DynFlags
+import StaticFlags
+import HscTypes
+import HsSyn
+import TcRnTypes
+import MkIface
+import Id
+import Name
 import CoreSyn
-import PprCore         ( pprRules, pprCoreExpr )
+import PprCore
 import DsMonad
-import DsExpr          ( dsLExpr )
-import DsBinds         ( dsTopLHsBinds, decomposeRuleLhs, AutoScc(..) )
-import DsForeign       ( dsForeigns )
+import DsExpr
+import DsBinds
+import DsForeign
 import DsExpr          ()      -- Forces DsExpr to be compiled; DsBinds only
                                -- depends on DsExpr.hi-boot.
 import Module
-import UniqFM          ( eltsUFM, delFromUFM )
-import PackageConfig   ( thPackageId )
-import RdrName         ( GlobalRdrEnv )
+import UniqFM
+import PackageConfig
+import RdrName
 import NameSet
 import VarSet
-import Rules           ( roughTopNames )
-import CoreLint                ( showPass, endPass )
-import CoreFVs         ( ruleRhsFreeVars, exprsFreeNames )
-import ErrUtils                ( doIfSet, dumpIfSet_dyn )
-import ListSetOps      ( insertList )
+import Rules
+import CoreLint
+import CoreFVs
+import ErrUtils
+import ListSetOps
 import Outputable
-import SrcLoc          ( Located(..) )
-import DATA_IOREF      ( readIORef )
-import Maybes          ( catMaybes )
+import SrcLoc
+import Maybes
 import FastString
-import Util            ( sortLe )
+import Util
+import Coverage
+
+import Data.IORef
 \end{code}
 
 %************************************************************************
@@ -52,10 +54,11 @@ import Util         ( sortLe )
 %************************************************************************
 
 \begin{code}
-deSugar :: HscEnv -> TcGblEnv -> IO (Maybe ModGuts)
+deSugar :: HscEnv -> ModLocation -> TcGblEnv -> IO (Maybe ModGuts)
 -- Can modify PCS by faulting in more declarations
 
 deSugar hsc_env 
+        mod_loc
         tcg_env@(TcGblEnv { tcg_mod       = mod,
                            tcg_src       = hsc_src,
                            tcg_type_env  = type_env,
@@ -76,24 +79,31 @@ deSugar hsc_env
   = do { showPass dflags "Desugar"
 
        -- Desugar the program
+        ; let export_set = availsToNameSet exports
+       ; let auto_scc = mkAutoScc mod export_set
+
        ; mb_res <- case ghcMode dflags of
-                    JustTypecheck -> return (Just ([], [], NoStubs))
-                    _             -> initDs hsc_env mod rdr_env type_env $ do
-                                       { core_prs <- dsTopLHsBinds auto_scc binds
+                    JustTypecheck -> return (Just ([], [], NoStubs, noHpcInfo))
+                     _        -> do (binds_cvr,ds_hpc_info) 
+                                             <- if opt_Hpc
+                                                 then addCoverageTicksToBinds dflags mod mod_loc binds
+                                                 else return (binds, noHpcInfo)
+                                    initDs hsc_env mod rdr_env type_env $ do
+                                       { core_prs <- dsTopLHsBinds auto_scc binds_cvr
                                        ; (ds_fords, foreign_prs) <- dsForeigns fords
                                        ; let all_prs = foreign_prs ++ core_prs
                                              local_bndrs = mkVarSet (map fst all_prs)
                                        ; ds_rules <- mappM (dsRule mod local_bndrs) rules
-                                       ; return (all_prs, catMaybes ds_rules, ds_fords)
+                                       ; return (all_prs, catMaybes ds_rules, ds_fords, ds_hpc_info)
                                        }
        ; case mb_res of {
           Nothing -> return Nothing ;
-          Just (all_prs, ds_rules, ds_fords) -> do
+          Just (all_prs, ds_rules, ds_fords,ds_hpc_info) -> do
 
        {       -- Add export flags to bindings
          keep_alive <- readIORef keep_var
-       ; let final_prs = addExportFlags ghci_mode exports keep_alive 
-                                        all_prs ds_rules
+       ; let final_prs = addExportFlags ghci_mode export_set
+                                 keep_alive all_prs ds_rules
              ds_binds  = [Rec final_prs]
        -- Notice that we put the whole lot in a big Rec, even the foreign binds
        -- When compiling PrelFloat, which defines data Float = F# Float#
@@ -135,9 +145,10 @@ deSugar hsc_env
             le_dep_mod :: (ModuleName, IsBootInterface) -> (ModuleName, IsBootInterface) -> Bool        
             le_dep_mod (m1,_) (m2,_) = moduleNameFS m1 <= moduleNameFS m2
 
-            deps = Deps { dep_mods  = sortLe le_dep_mod dep_mods,
-                          dep_pkgs  = sortLe (<=)   pkgs,      
-                          dep_orphs = sortLe le_mod (imp_orphs imports) }
+            deps = Deps { dep_mods   = sortLe le_dep_mod dep_mods,
+                          dep_pkgs   = sortLe (<=)   pkgs,     
+                          dep_orphs  = sortLe le_mod (imp_orphs  imports),
+                          dep_finsts = sortLe le_mod (imp_finsts imports) }
                -- sort to get into canonical order
 
             mod_guts = ModGuts {       
@@ -155,16 +166,26 @@ deSugar hsc_env
                mg_fam_insts = fam_insts,
                mg_rules     = ds_rules,
                mg_binds     = ds_binds,
-               mg_foreign   = ds_fords }
-       
+               mg_foreign   = ds_fords,
+               mg_hpc_info  = ds_hpc_info }
         ; return (Just mod_guts)
        }}}
 
   where
     dflags    = hsc_dflags hsc_env
     ghci_mode = ghcMode (hsc_dflags hsc_env)
-    auto_scc | opt_SccProfilingOn = TopLevel
-            | otherwise          = NoSccs
+
+mkAutoScc :: Module -> NameSet -> AutoScc
+mkAutoScc mod exports
+  | not opt_SccProfilingOn     -- No profiling
+  = NoSccs             
+  | opt_AutoSccsOnAllToplevs   -- Add auto-scc on all top-level things
+  = AddSccs mod (\id -> True)
+  | opt_AutoSccsOnExportedToplevs      -- Only on exported things
+  = AddSccs mod (\id -> idName id `elemNameSet` exports)
+  | otherwise
+  = NoSccs
+
 
 deSugarExpr :: HscEnv
            -> Module -> GlobalRdrEnv -> TypeEnv