Add 'rec' to stmts in a 'do', and deprecate 'mdo'
[ghc-hetmet.git] / compiler / main / TidyPgm.lhs
index 7551494..e87bac6 100644 (file)
@@ -303,8 +303,10 @@ tidyProgram hsc_env  (ModGuts { mg_module = mod, mg_exports = exports,
              ; th         = dopt Opt_TemplateHaskell      dflags
               }
 
+       ; let { implicit_binds = getImplicitBinds type_env }
+
         ; (unfold_env, tidy_occ_env)
-              <- chooseExternalIds hsc_env mod omit_prags binds
+              <- chooseExternalIds hsc_env mod omit_prags binds implicit_binds
 
         ; let { ext_rules 
                   | omit_prags = []
@@ -338,7 +340,6 @@ tidyProgram hsc_env  (ModGuts { mg_module = mod, mg_exports = exports,
                -- empty
 
              -- See Note [Injecting implicit bindings]
-             ; implicit_binds = getImplicitBinds type_env
              ; all_tidy_binds = implicit_binds ++ tidy_binds
 
              ; alg_tycons = filter isAlgTyCon (typeEnvTyCons type_env)
@@ -495,6 +496,11 @@ why CoreUnfold.mkImplicitUnfolding uses simleExprOpt to do a bit of
 optimisation first.  (Only matters when the selector is used curried;
 eg map x ys.)  See Trac #2070.
 
+[Oct 09: in fact, record selectors are no longer implicit Ids at all,
+because we really do want to optimise them properly. They are treated
+much like any other Id.  But doing "light" optimisation on an implicit
+Id still makes sense.]
+
 At one time I tried injecting the implicit bindings *early*, at the
 beginning of SimplCore.  But that gave rise to real difficulty,
 becuase GlobalIds are supposed to have *fixed* IdInfo, but the
@@ -505,18 +511,23 @@ importing modules were expecting it to have arity 1 (Trac #2844).
 It's much safer just to inject them right at the end, after tidying.
 
 Oh: two other reasons for injecting them late:
+
   - If implicit Ids are already in the bindings when we start TidyPgm,
     we'd have to be careful not to treat them as external Ids (in
     the sense of findExternalIds); else the Ids mentioned in *their*
     RHSs will be treated as external and you get an interface file 
     saying      a18 = <blah>
     but nothing refererring to a18 (because the implicit Id is the 
-    one that does).
+    one that does, and implicit Ids don't appear in interface files).
 
   - More seriously, the tidied type-envt will include the implicit
     Id replete with a18 in its unfolding; but we won't take account
     of a18 when computing a fingerprint for the class; result chaos.
     
+There is one sort of implicit binding that is injected still later,
+namely those for data constructor workers. Reason (I think): it's
+really just a code generation trick.... binding itself makes no sense.
+See CorePrep Note [Data constructor workers].
 
 \begin{code}
 getImplicitBinds :: TypeEnv -> [CoreBind]
@@ -552,10 +563,11 @@ chooseExternalIds :: HscEnv
                   -> Module
                   -> Bool
                  -> [CoreBind]
+                  -> [CoreBind]
                   -> IO (UnfoldEnv, TidyOccEnv)
        -- Step 1 from the notes above
 
-chooseExternalIds hsc_env mod omit_prags binds
+chooseExternalIds hsc_env mod omit_prags binds implicit_binds
   = do
     (unfold_env1,occ_env1) 
         <- search (zip sorted_exports sorted_exports) emptyVarEnv init_occ_env
@@ -576,11 +588,12 @@ chooseExternalIds hsc_env mod omit_prags binds
                      filter isExportedId binders
 
   binders = bindersOfBinds binds
+  implicit_binders = bindersOfBinds implicit_binds
 
   bind_env :: IdEnv (Id,CoreExpr)
   bind_env = mkVarEnv (zip (map fst bs) bs) where bs = flattenBinds binds
 
-  avoids   = [getOccName name | bndr <- binders,
+  avoids   = [getOccName name | bndr <- binders ++ implicit_binders,
                                 let name = idName bndr,
                                 isExternalName name ]
                -- In computing our "avoids" list, we must include
@@ -589,6 +602,8 @@ chooseExternalIds hsc_env mod omit_prags binds
                --                                      all by the renamer)
                -- since their names are "taken".
                -- The type environment is a convenient source of such things.
+                -- In particular, the set of binders doesn't include
+                -- implicit Ids at this stage.
 
        -- We also make sure to avoid any exported binders.  Consider
        --      f{-u1-} = 1     -- Local decl