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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/c3cf0419bbec99086e9ed63d4ba324639ba65fb8

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

commit c3cf0419bbec99086e9ed63d4ba324639ba65fb8
Merge: bfe9401... 96a3768...
Author: Ian Lynagh <[email protected]>
Date:   Wed Jun 13 13:14:41 2012 +0100

    Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
    
    Fix conflicts in:
        compiler/main/DynFlags.hs

 compiler/cmm/Bitmap.hs              |    2 +-
 compiler/ghci/ByteCodeGen.lhs       |  104 +++++++++-----
 compiler/main/DynFlags.hs           |   29 ++--
 compiler/main/HscMain.hs            |   16 +-
 compiler/main/HscTypes.lhs          |   22 ++--
 compiler/parser/Lexer.x             |    7 +-
 compiler/rename/RnExpr.lhs          |   25 ++--
 compiler/typecheck/TcRnTypes.lhs    |    5 +-
 compiler/typecheck/TcTyClsDecls.lhs |   11 +-
 docs/comm/genesis/modules.html      |    2 +-
 docs/users_guide/flags.xml          |    8 +-
 docs/users_guide/glasgow_exts.xml   |  267 +++++++++++++++++++++--------------
 ghc/InteractiveUI.hs                |    2 +-
 rts/Linker.c                        |    2 +-
 14 files changed, 297 insertions(+), 205 deletions(-)

diff --cc compiler/main/DynFlags.hs
index b832480,5775c35..f576519
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@@ -377,18 -373,15 +377,18 @@@ data SafeHaskellMod
     | Sf_Unsafe
     | Sf_Trustworthy
     | Sf_Safe
-    | Sf_SafeInfered
+    | Sf_SafeInferred
     deriving (Eq)
  
 +instance Show SafeHaskellMode where
 +    show Sf_None        = "None"
 +    show Sf_Unsafe      = "Unsafe"
 +    show Sf_Trustworthy = "Trustworthy"
 +    show Sf_Safe        = "Safe"
 +    show Sf_SafeInfered = "Safe-Infered"
 +
  instance Outputable SafeHaskellMode where
 -    ppr Sf_None         = ptext $ sLit "None"
 -    ppr Sf_Unsafe       = ptext $ sLit "Unsafe"
 -    ppr Sf_Trustworthy  = ptext $ sLit "Trustworthy"
 -    ppr Sf_Safe         = ptext $ sLit "Safe"
 -    ppr Sf_SafeInferred = ptext $ sLit "Safe-Inferred"
 +    ppr = text . show
  
  data ExtensionFlag
     = Opt_Cpp
@@@ -1190,14 -1168,14 +1189,14 @@@ safeImplicitImpsReq d = safeLanguageOn 
  -- want to export this functionality from the module but do want to export the
  -- type constructors.
  combineSafeFlags :: SafeHaskellMode -> SafeHaskellMode -> DynP SafeHaskellMode
- combineSafeFlags a b | a == Sf_SafeInfered = return b
-                      | b == Sf_SafeInfered = return a
-                      | a == Sf_None        = return b
-                      | b == Sf_None        = return a
-                      | a == b              = return a
-                      | otherwise           = addErr errm >> return (panic 
errm)
+ combineSafeFlags a b | a == Sf_SafeInferred = return b
+                      | b == Sf_SafeInferred = return a
+                      | a == Sf_None         = return b
+                      | b == Sf_None         = return a
+                      | a == b               = return a
+                      | otherwise            = addErr errm >> return (panic 
errm)
      where errm = "Incompatible Safe Haskell flags! ("
 -                    ++ showPpr a ++ ", " ++ showPpr b ++ ")"
 +                    ++ show a ++ ", " ++ show b ++ ")"
  
  -- | A list of unsafe flags under Safe Haskell. Tuple elements are:
  --     * name of the flag
diff --cc compiler/main/HscMain.hs
index 5a90f2a,fdef710..0c0b3d9
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@@ -926,9 -925,9 +926,9 @@@ hscCheckSafeImports tcg_env = d
                -- user defined RULES, so not safe or already unsafe
              | safeInferOn dflags && not (null $ tcg_rules tcg_env') ||
                safeHaskell dflags == Sf_None
 -            -> wipeTrust tcg_env' $ warns (tcg_rules tcg_env')
 +            -> wipeTrust tcg_env' $ warns dflags (tcg_rules tcg_env')
  
-               -- trustworthy OR safe infered with no RULES
+               -- trustworthy OR safe inferred with no RULES
              | otherwise
              -> return tcg_env'
  



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

Reply via email to