Hi Ian,

Could you pull these two patches into 7.4 branch please:

commit 82e19ffc86a77b4b6eb4ea35636c7737b7e68202
Author: David Terei <[email protected]>
Date:   Mon Dec 19 18:37:47 2011 -0800

    Ignore -fpackage-trust if no other Safe Haskell flags

commit 4ff7d0bb9d3e627843e601e6a0a623a6b03783a2
Author: David Terei <[email protected]>
Date:   Fri Dec 16 13:45:53 2011 -0800

    Refactor Safe Haskell check to provide hscCheckSafe GHC API

Cheers,
David


On 20 December 2011 00:51, David Terei <[email protected]> wrote:
> Repository : ssh://darcs.haskell.org//srv/darcs/ghc
>
> On branch  : master
>
> http://hackage.haskell.org/trac/ghc/changeset/82e19ffc86a77b4b6eb4ea35636c7737b7e68202
>
>>---------------------------------------------------------------
>
> commit 82e19ffc86a77b4b6eb4ea35636c7737b7e68202
> Author: David Terei <[email protected]>
> Date:   Mon Dec 19 18:37:47 2011 -0800
>
>    Ignore -fpackage-trust if no other Safe Haskell flags
>
>>---------------------------------------------------------------
>
>  compiler/main/DynFlags.hs |   35 ++++++++++++++++++++++++++---------
>  1 files changed, 26 insertions(+), 9 deletions(-)
>
> diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
> index 8e2b714..1bd4fce 100644
> --- a/compiler/main/DynFlags.hs
> +++ b/compiler/main/DynFlags.hs
> @@ -564,11 +564,12 @@ data DynFlags = DynFlags {
>   language              :: Maybe Language,
>   -- | Safe Haskell mode
>   safeHaskell           :: SafeHaskellMode,
> -  -- We store the location of where template haskell and newtype deriving 
> were
> -  -- turned on so we can produce accurate error messages when Safe Haskell 
> turns
> -  -- them off.
> +  -- We store the location of where some extension and flags were turned on 
> so
> +  -- we can produce accurate error messages when Safe Haskell fails due to
> +  -- them.
>   thOnLoc               :: SrcSpan,
>   newDerivOnLoc         :: SrcSpan,
> +  pkgTrustOnLoc         :: SrcSpan,
>   warnSafeOnLoc         :: SrcSpan,
>   warnUnsafeOnLoc       :: SrcSpan,
>   -- Don't change this without updating extensionFlags:
> @@ -911,6 +912,7 @@ defaultDynFlags mySettings =
>         safeHaskell = Sf_SafeInfered,
>         thOnLoc = noSrcSpan,
>         newDerivOnLoc = noSrcSpan,
> +        pkgTrustOnLoc = noSrcSpan,
>         warnSafeOnLoc = noSrcSpan,
>         warnUnsafeOnLoc = noSrcSpan,
>         extensions = [],
> @@ -1306,19 +1308,28 @@ parseDynamicFlags dflags0 args cmdline = do
>   when (not (null errs)) $ ghcError $ errorsToGhcException errs
>
>   -- check for disabled flags in safe haskell
> -  let (dflags2, sh_warns) = safeFlagCheck dflags1
> +  let (dflags2, sh_warns) = safeFlagCheck cmdline dflags1
>
>   return (dflags2, leftover, sh_warns ++ warns)
>
>  -- | Check (and potentially disable) any extensions that aren't allowed
>  -- in safe mode.
> -safeFlagCheck :: DynFlags -> (DynFlags, [Located String])
> -safeFlagCheck dflags | not (safeLanguageOn dflags || safeInferOn dflags)
> -                     = (dflags, [])
> -safeFlagCheck dflags =
> +safeFlagCheck :: Bool -> DynFlags -> (DynFlags, [Located String])
> +safeFlagCheck _  dflags | not (safeLanguageOn dflags || safeInferOn dflags)
> +                        = (dflags, [])
> +
> +safeFlagCheck cmdl dflags =
>     case safeLanguageOn dflags of
>         True -> (dflags', warns)
>
> +        -- throw error if -fpackage-trust by itself with no safe haskell flag
> +        False | not cmdl && safeInferOn dflags && packageTrustOn dflags
> +              -> (dopt_unset dflags' Opt_PackageTrust,
> +                  [L (pkgTrustOnLoc dflags') $
> +                      "Warning: -fpackage-trust ignored;" ++
> +                      " must be specified with a Safe Haskell flag"]
> +                  )
> +
>         False | null warns && safeInfOk
>               -> (dflags', [])
>
> @@ -1664,7 +1675,7 @@ dynamic_flags = [
>   , Flag "fno-glasgow-exts" (NoArg (disableGlasgowExts >> deprecate "Use 
> individual extensions instead"))
>
>         ------ Safe Haskell flags -------------------------------------------
> -  , Flag "fpackage-trust"   (NoArg (setDynFlag Opt_PackageTrust))
> +  , Flag "fpackage-trust"   (NoArg setPackageTrust)
>   , Flag "fno-safe-infer"   (NoArg (setSafeHaskell Sf_None))
>  ]
>  ++ map (mkFlag turnOn  "f"    setDynFlag  ) fFlags
> @@ -2177,6 +2188,12 @@ setWarnUnsafe :: Bool -> DynP ()
>  setWarnUnsafe True  = getCurLoc >>= \l -> upd (\d -> d { warnUnsafeOnLoc = l 
> })
>  setWarnUnsafe False = return ()
>
> +setPackageTrust :: DynP ()
> +setPackageTrust = do
> +    setDynFlag Opt_PackageTrust
> +    l <- getCurLoc
> +    upd $ \d -> d { pkgTrustOnLoc = l }
> +
>  setGenDeriving :: Bool -> DynP ()
>  setGenDeriving True  = getCurLoc >>= \l -> upd (\d -> d { newDerivOnLoc = l 
> })
>  setGenDeriving False = return ()
>
>
>
> _______________________________________________
> Cvs-ghc mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/cvs-ghc

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

Reply via email to