Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/94434054df5633fc7aef9aad37aa26c8b2e011cd

>---------------------------------------------------------------

commit 94434054df5633fc7aef9aad37aa26c8b2e011cd
Author: David Terei <[email protected]>
Date:   Mon Apr 25 12:18:00 2011 -0700

    SafeHaskell: Force all imports to be safe in Safe mode

>---------------------------------------------------------------

 compiler/iface/MkIface.lhs  |    8 +++++---
 compiler/main/DynFlags.hs   |    9 ++++++++-
 compiler/rename/RnNames.lhs |    6 ++++--
 3 files changed, 17 insertions(+), 6 deletions(-)

diff --git a/compiler/iface/MkIface.lhs b/compiler/iface/MkIface.lhs
index 6ff9191..bd727da 100644
--- a/compiler/iface/MkIface.lhs
+++ b/compiler/iface/MkIface.lhs
@@ -907,9 +907,11 @@ mk_usage_info pit hsc_env this_mod direct_imports 
used_names
 
         (is_direct_import, imp_safe)
             = case lookupModuleEnv direct_imports mod of
-                Just ((_,_,_,safe):xs) -> (True, safe)
-                Just _                 -> pprPanic "mkUsage: empty direct 
import" empty
-                Nothing                -> (False, False)
+                Just ((_,_,_,safe):_xs) -> (True, safe)
+                Just _                  -> pprPanic "mkUsage: empty direct 
import" empty
+                Nothing                 -> (False, safeImportsRequired dflags)
+                -- Nothing case is for implicit imports like 'System.IO' when 
'putStrLn'
+                -- is used in the source code. We require them to be safe in 
SafeHaskell
     
         used_occs = lookupModuleEnv ent_map mod `orElse` []
 
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index bb91170..30ad0ad 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -31,8 +31,10 @@ module DynFlags (
         fFlags, fLangFlags, xFlags,
         DPHBackend(..), dphPackageMaybe,
         wayNames,
+
+        -- ** SafeHaskell
         SafeHaskellMode(..),
-        safeHaskellOn,
+        safeHaskellOn, safeImportsRequired,
 
         Settings(..),
         ghcUsagePath, ghciUsagePath, topDir, tmpDir, rawSettings,
@@ -985,6 +987,11 @@ setSafeHaskell s = upd f
                          safeHaskell = combineSafeFlags sf s
                      }
 
+-- | Are all imports required to be safe for this SafeHaskell mode?
+safeImportsRequired :: DynFlags -> Bool
+safeImportsRequired dflags = m == Sf_SafeLanguage || m == Sf_Safe
+                            where m = safeHaskell dflags
+
 -- | Combine two SafeHaskell modes correctly. Used for dealing with multiple 
flags.
 -- This makes SafeHaskell very much a monoid but for now I prefer this as I 
don't
 -- want to export this functionality from the module but do want to export the
diff --git a/compiler/rename/RnNames.lhs b/compiler/rename/RnNames.lhs
index 57166f4..cd1cff6 100644
--- a/compiler/rename/RnNames.lhs
+++ b/compiler/rename/RnNames.lhs
@@ -219,8 +219,10 @@ rnImportDecl this_mod implicit_prelude
                         Just (is_hiding, ls) -> not is_hiding && null ls
                         _                    -> False
 
+        mod_safe' = mod_safe || safeImportsRequired dflags
+
         imports   = ImportAvails {
-                        imp_mods     = unitModuleEnv imp_mod [(qual_mod_name, 
import_all, loc, mod_safe)],
+                        imp_mods     = unitModuleEnv imp_mod [(qual_mod_name, 
import_all, loc, mod_safe')],
                         imp_orphs    = orphans,
                         imp_finsts   = finsts,
                         imp_dep_mods = mkModDeps dependent_mods,
@@ -234,7 +236,7 @@ rnImportDecl this_mod implicit_prelude
           _           -> return ()
      )
 
-    let new_imp_decl = L loc (ImportDecl loc_imp_mod_name mb_pkg want_boot 
mod_safe
+    let new_imp_decl = L loc (ImportDecl loc_imp_mod_name mb_pkg want_boot 
mod_safe'
                                          qual_only as_mod new_imp_details)
 
     return (new_imp_decl, gbl_env, imports, mi_hpc iface)



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to