Another round of External Core fixes
[ghc-hetmet.git] / compiler / main / TidyPgm.lhs
index e327996..64f3498 100644 (file)
@@ -20,7 +20,7 @@ import CoreLint
 import CoreUtils
 import VarEnv
 import VarSet
-import Var
+import Var hiding( mkGlobalId )
 import Id
 import IdInfo
 import InstEnv
@@ -34,21 +34,17 @@ import OccName
 import TcType
 import DataCon
 import TyCon
-import Class
 import Module
 import HscTypes
 import Maybes
 import ErrUtils
 import UniqSupply
 import Outputable
-import FastTypes hiding (fastOr)
+import FastBool hiding ( fastOr )
 
 import Data.List       ( partition )
 import Data.Maybe      ( isJust )
 import Data.IORef      ( IORef, readIORef, writeIORef )
-
-_dummy :: FS.FastString
-_dummy = FSLIT("")
 \end{code}
 
 
@@ -138,10 +134,9 @@ mkBootModDetails hsc_env exports type_env insts fam_insts
        ; showPass dflags "Tidy [hoot] type env"
 
        ; let { insts'     = tidyInstances tidyExternalId insts
-             ; type_env1  = filterNameEnv (not . isWiredInThing) type_env
-             ; type_env2  = mapNameEnv tidyBootThing type_env1
-             ; type_env'  = extendTypeEnvWithIds type_env2
-                               (map instanceDFunId insts')
+             ; dfun_ids   = map instanceDFunId insts'
+             ; type_env1  = tidyBootTypeEnv (availsToNameSet exports) type_env
+             ; type_env'  = extendTypeEnvWithIds type_env1 dfun_ids
              }
        ; return (ModDetails { md_types     = type_env'
                             , md_insts     = insts'
@@ -153,13 +148,27 @@ mkBootModDetails hsc_env exports type_env insts fam_insts
        }
   where
 
-isWiredInThing :: TyThing -> Bool
-isWiredInThing thing = isWiredInName (getName thing)
+tidyBootTypeEnv :: NameSet -> TypeEnv -> TypeEnv
+tidyBootTypeEnv exports type_env 
+  = tidyTypeEnv True exports type_env final_ids
+  where
+       -- Find the LocalIds in the type env that are exported
+       -- Make them into GlobalIds, and tidy their types
+       --
+       -- It's very important to remove the non-exported ones
+       -- because we don't tidy the OccNames, and if we don't remove
+       -- the non-exported ones we'll get many things with the
+       -- same name in the interface file, giving chaos.
+    final_ids = [ tidyExternalId id
+               | id <- typeEnvIds type_env
+               , isLocalId id
+               , keep_it id ]
+
+        -- default methods have their export flag set, but everything
+        -- else doesn't (yet), because this is pre-desugaring, so we
+        -- must test both.
+    keep_it id = isExportedId id || idName id `elemNameSet` exports
 
-tidyBootThing :: TyThing -> TyThing
--- Just externalise the Ids; keep everything
-tidyBootThing (AnId id) | isLocalId id = AnId (tidyExternalId id)
-tidyBootThing thing                   = thing
 
 tidyExternalId :: Id -> Id
 -- Takes an LocalId with an External Name, 
@@ -277,8 +286,10 @@ tidyProgram hsc_env
                                                 binds
 
        ; let { export_set = availsToNameSet exports
+             ; final_ids  = [ id | id <- bindersOfBinds tidy_binds, 
+                                   isExternalName (idName id)]
               ; tidy_type_env = tidyTypeEnv omit_prags export_set type_env 
-                                           tidy_binds
+                                           final_ids
              ; tidy_insts    = tidyInstances (lookup_dfun tidy_type_env) insts
                -- A DFunId will have a binding in tidy_binds, and so
                -- will now be in final_env, replete with IdInfo
@@ -291,12 +302,10 @@ tidyProgram hsc_env
                -- and indeed it does, but if omit_prags is on, ext_rules is
                -- empty
 
-             ; implicit_binds = getImplicitBinds type_env
-             ; all_tidy_binds = implicit_binds ++ tidy_binds
              ; alg_tycons = filter isAlgTyCon (typeEnvTyCons type_env)
              }
 
-       ; endPass dflags "Tidy Core" Opt_D_dump_simpl all_tidy_binds
+       ; endPass dflags "Tidy Core" Opt_D_dump_simpl tidy_binds
        ; dumpIfSet_core dflags Opt_D_dump_simpl
                "Tidy Core Rules"
                (pprRules tidy_rules)
@@ -305,7 +314,7 @@ tidyProgram hsc_env
 
        ; return (CgGuts { cg_module   = mod, 
                           cg_tycons   = alg_tycons,
-                          cg_binds    = all_tidy_binds,
+                          cg_binds    = tidy_binds,
                           cg_dir_imps = dir_imp_mods,
                           cg_foreign  = foreign_stubs,
                           cg_dep_pkgs = dep_pkgs deps,
@@ -327,7 +336,8 @@ lookup_dfun type_env dfun_id
        Just (AnId dfun_id') -> dfun_id'
        _other -> pprPanic "lookup_dfun" (ppr dfun_id)
 
-tidyTypeEnv :: Bool -> NameSet -> TypeEnv -> [CoreBind] -> TypeEnv
+--------------------------
+tidyTypeEnv :: Bool -> NameSet -> TypeEnv -> [Id] -> TypeEnv
 
 -- The competed type environment is gotten from
 --     Dropping any wired-in things, and then
@@ -341,17 +351,14 @@ tidyTypeEnv :: Bool -> NameSet -> TypeEnv -> [CoreBind] -> TypeEnv
 -- This truncates the type environment to include only the 
 -- exported Ids and things needed from them, which saves space
 
-tidyTypeEnv omit_prags exports type_env tidy_binds
+tidyTypeEnv omit_prags exports type_env final_ids
   = let type_env1 = filterNameEnv keep_it type_env
        type_env2 = extendTypeEnvWithIds type_env1 final_ids
-       type_env3 | omit_prags = mapNameEnv trim_thing type_env2
+       type_env3 | omit_prags = mapNameEnv (trimThing exports) type_env2
                  | otherwise  = type_env2
     in 
     type_env3
   where
-    final_ids  = [ id | id <- bindersOfBinds tidy_binds, 
-                       isExternalName (idName id)]
-
        -- We keep GlobalIds, because they won't appear 
        -- in the bindings from which final_ids are derived!
        -- (The bindings bind LocalIds.)
@@ -359,15 +366,24 @@ tidyTypeEnv omit_prags exports type_env tidy_binds
     keep_it (AnId id) = isGlobalId id  -- Keep GlobalIds (e.g. class ops)
     keep_it _other    = True           -- Keep all TyCons, DataCons, and Classes
 
-    trim_thing thing
-       = case thing of
-           ATyCon tc | mustExposeTyCon exports tc -> thing
-                     | otherwise -> ATyCon (makeTyConAbstract tc)
+--------------------------
+isWiredInThing :: TyThing -> Bool
+isWiredInThing thing = isWiredInName (getName thing)
+
+--------------------------
+trimThing :: NameSet -> TyThing -> TyThing
+-- Trim off inessentials, for boot files and no -O
+trimThing exports (ATyCon tc)
+   | not (mustExposeTyCon exports tc)
+   = ATyCon (makeTyConAbstract tc)
 
-           AnId id | isImplicitId id -> thing
-                   | otherwise       -> AnId (id `setIdInfo` vanillaIdInfo)
+trimThing _exports (AnId id)
+   | not (isImplicitId id) 
+   = AnId (id `setIdInfo` vanillaIdInfo)
+
+trimThing _exports other_thing 
+  = other_thing
 
-           _other -> thing
 
 mustExposeTyCon :: NameSet     -- Exports
                -> TyCon        -- The tycon
@@ -381,13 +397,14 @@ mustExposeTyCon exports tc
   | isEnumerationTyCon tc      -- For an enumeration, exposing the constructors
   = True                       -- won't lead to the need for further exposure
                                -- (This includes data types with no constructors.)
-  | isOpenTyCon tc             -- open type family
+  | isOpenTyCon tc             -- Open type family
   = True
+
   | otherwise                  -- Newtype, datatype
   = any exported_con (tyConDataCons tc)
        -- Expose rep if any datacon or field is exported
 
-  || (isNewTyCon tc && isFFITy (snd (newTyConRep tc)))
+  || (isNewTyCon tc && isFFITy (snd (newTyConRhs tc)))
        -- Expose the rep for newtypes if the rep is an FFI type.  
        -- For a very annoying reason.  'Foreign import' is meant to
        -- be able to look through newtypes transparently, but it
@@ -402,31 +419,6 @@ tidyInstances tidy_dfun ispecs
   where
     tidy ispec = setInstanceDFunId ispec $
                 tidy_dfun (instanceDFunId ispec)
-
-getImplicitBinds :: TypeEnv -> [CoreBind]
-getImplicitBinds type_env
-  = map get_defn (concatMap implicit_con_ids (typeEnvTyCons type_env)
-                 ++ concatMap other_implicit_ids (typeEnvElts type_env))
-       -- Put the constructor wrappers first, because
-       -- other implicit bindings (notably the fromT functions arising 
-       -- from generics) use the constructor wrappers.  At least that's
-       -- what External Core likes
-  where
-    implicit_con_ids tc = mapCatMaybes dataConWrapId_maybe (tyConDataCons tc)
-    
-    other_implicit_ids (ATyCon tc) = filter (not . isNaughtyRecordSelector) (tyConSelIds tc)
-       -- The "naughty" ones are not real functions at all
-       -- They are there just so we can get decent error messages
-       -- See Note  [Naughty record selectors] in MkId.lhs
-    other_implicit_ids (AClass cl) = classSelIds cl
-    other_implicit_ids _other      = []
-    
-    get_defn :: Id -> CoreBind
-    get_defn id = NonRec id (tidyExpr emptyTidyEnv rhs)
-       where
-         rhs = unfoldingTemplate (idUnfolding id)
-       -- Don't forget to tidy the body !  Otherwise you get silly things like
-       --      \ tpl -> case tpl of tpl -> (tpl,tpl) -> tpl
 \end{code}
 
 
@@ -721,12 +713,13 @@ tidyTopPair :: VarEnv Bool
        -- in the IdInfo of one early in the group
 
 tidyTopPair ext_ids rhs_tidy_env caf_info name' (bndr, rhs)
-  | isGlobalId bndr            -- Injected binding for record selector, etc
-  = (bndr, tidyExpr rhs_tidy_env rhs)
-  | otherwise
   = (bndr', rhs')
   where
-    bndr'   = mkVanillaGlobal name' ty' idinfo'
+    bndr' = mkGlobalId details name' ty' idinfo'
+       -- Preserve the GlobalIdDetails of existing global-ids
+    details = case globalIdDetails bndr of     
+               NotGlobalId -> VanillaGlobal
+               old_details -> old_details
     ty'            = tidyTopType (idType bndr)
     rhs'    = tidyExpr rhs_tidy_env rhs
     idinfo  = idInfo bndr
@@ -795,7 +788,7 @@ tidyWorker _tidy_env _show_unfold NoWorker
   = NoWorker
 tidyWorker tidy_env show_unfold (HasWorker work_id wrap_arity) 
   | show_unfold = HasWorker (tidyVarOcc tidy_env work_id) wrap_arity
-  | otherwise   = WARN( True, ppr work_id ) NoWorker
+  | otherwise   = NoWorker
     -- NB: do *not* expose the worker if show_unfold is off,
     --     because that means this thing is a loop breaker or
     --     marked NOINLINE or something like that
@@ -803,8 +796,12 @@ tidyWorker tidy_env show_unfold (HasWorker work_id wrap_arity)
     -- then you can make the simplifier go into an infinite loop, because
     -- in effect the unfolding is exposed.  See Trac #1709
     -- 
-    -- Mind you, it probably should not be w/w'd in the first place; 
-    -- hence the WARN
+    -- You might think that if show_unfold is False, then the thing should
+    -- not be w/w'd in the first place.  But a legitimate reason is this:
+    --           the function returns bottom
+    -- In this case, show_unfold will be false (we don't expose unfoldings
+    -- for bottoming functions), but we might still have a worker/wrapper
+    -- split (see Note [Worker-wrapper for bottoming functions] in WorkWrap.lhs
 \end{code}
 
 %************************************************************************