[commit: ghc] wip/T16193, wip/fix-json-profiling-report-i386: Add `-fplugin-trustworthy` to avoid marking modules as unsafe (406e43a)

git at git.haskell.org git at git.haskell.org
Tue Feb 5 12:23:49 UTC 2019


Repository : ssh://git@git.haskell.org/ghc

On branches: wip/T16193,wip/fix-json-profiling-report-i386
Link       : http://ghc.haskell.org/trac/ghc/changeset/406e43af2f12756c80d583b86326f760f2f584cc/ghc

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

commit 406e43af2f12756c80d583b86326f760f2f584cc
Author: Zejun Wu <watashi at fb.com>
Date:   Wed Jan 30 22:13:42 2019 -0800

    Add `-fplugin-trustworthy` to avoid marking modules as unsafe
    
    By default, when a module is compiled with plugins, it will be marked as
    unsafe. With this flag passed, all plugins are treated as trustworthy
    and the safety inference will no longer be affected.
    
    This fixes Trac #16260.


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

406e43af2f12756c80d583b86326f760f2f584cc
 compiler/main/DynFlags.hs                               |  3 +++
 compiler/main/Plugins.hs                                |  8 +++++---
 compiler/typecheck/TcRnDriver.hs                        |  3 ++-
 docs/users_guide/extending_ghc.rst                      | 10 ++++++++++
 testsuite/tests/plugins/Makefile                        |  5 +++++
 testsuite/tests/plugins/T16260.hs                       |  1 +
 .../bkprun04.stdout => plugins/T16260.stdout}           |  2 ++
 testsuite/tests/plugins/all.T                           |  6 ++++++
 .../plugins/simple-plugin/Simple/TrustworthyPlugin.hs   | 17 +++++++++++++++++
 .../tests/plugins/simple-plugin/simple-plugin.cabal     |  1 +
 10 files changed, 52 insertions(+), 4 deletions(-)

diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 28d8bf8..a9b4a03 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -648,6 +648,7 @@ data GeneralFlag
    -- safe haskell flags
    | Opt_DistrustAllPackages
    | Opt_PackageTrust
+   | Opt_PluginTrustworthy
 
    | Opt_G_NoStateHack
    | Opt_G_NoOptCoercion
@@ -3512,6 +3513,8 @@ dynamic_flags_deps = [
 
         ------ Plugin flags ------------------------------------------------
   , make_ord_flag defGhcFlag "fplugin-opt" (hasArg addPluginModuleNameOption)
+  , make_ord_flag defGhcFlag "fplugin-trustworthy"
+      (NoArg (setGeneralFlag Opt_PluginTrustworthy))
   , make_ord_flag defGhcFlag "fplugin"     (hasArg addPluginModuleName)
   , make_ord_flag defGhcFlag "fclear-plugins" (noArg clearPluginModuleNames)
   , make_ord_flag defGhcFlag "ffrontend-opt" (hasArg addFrontendPluginOption)
diff --git a/compiler/main/Plugins.hs b/compiler/main/Plugins.hs
index de04415..585eab1 100644
--- a/compiler/main/Plugins.hs
+++ b/compiler/main/Plugins.hs
@@ -91,7 +91,7 @@ data Plugin = Plugin {
     -- `HsGroup` has been renamed.
   , typeCheckResultAction :: [CommandLineOption] -> ModSummary -> TcGblEnv
                                -> TcM TcGblEnv
-    -- ^ Modify the module when it is type checked. This is called add the
+    -- ^ Modify the module when it is type checked. This is called at the
     -- very end of typechecking.
   , spliceRunAction :: [CommandLineOption] -> LHsExpr GhcTc
                          -> TcM (LHsExpr GhcTc)
@@ -178,8 +178,10 @@ impurePlugin _args = return ForceRecompile
 flagRecompile =
   return . MaybeRecompile . fingerprintFingerprints . map fingerprintString . sort
 
--- | Default plugin: does nothing at all! For compatibility reasons
--- you should base all your plugin definitions on this default value.
+-- | Default plugin: does nothing at all, except for marking that safe
+-- inference has failed unless @-fplugin-trustworthy@ is passed. For
+-- compatibility reaso you should base all your plugin definitions on this
+-- default value.
 defaultPlugin :: Plugin
 defaultPlugin = Plugin {
         installCoreToDos      = const return
diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs
index 36ec8dc..c76a486 100644
--- a/compiler/typecheck/TcRnDriver.hs
+++ b/compiler/typecheck/TcRnDriver.hs
@@ -2901,7 +2901,8 @@ runTypecheckerPlugin sum hsc_env gbl_env = do
       gbl_env
 
 mark_plugin_unsafe :: DynFlags -> TcM ()
-mark_plugin_unsafe dflags = recordUnsafeInfer pluginUnsafe
+mark_plugin_unsafe dflags = unless (gopt Opt_PluginTrustworthy dflags) $
+  recordUnsafeInfer pluginUnsafe
   where
     unsafeText = "Use of plugins makes the module unsafe"
     pluginUnsafe = unitBag ( mkPlainWarnMsg dflags noSrcSpan
diff --git a/docs/users_guide/extending_ghc.rst b/docs/users_guide/extending_ghc.rst
index 04bb2df..b1f7b60 100644
--- a/docs/users_guide/extending_ghc.rst
+++ b/docs/users_guide/extending_ghc.rst
@@ -216,6 +216,16 @@ be reset with the :ghc-flag:`-fclear-plugins` option.
     Give arguments to a plugin module; module must be specified with
     :ghc-flag:`-fplugin=⟨module⟩`.
 
+.. ghc-flag:: -fplugin-trustworthy
+    :shortdesc: Trust the used plugins and no longer mark the compiled module
+        as unsafe
+    :type: dynamic
+    :category: plugins
+
+    By default, when a module is compiled with plugins, it will be marked as
+    unsafe. With this flag passed, all plugins are treated as trustworthy
+    and the safety inference will no longer be affected.
+
 .. ghc-flag:: -fclear-plugins
     :shortdesc: Clear the list of active plugins
     :type: dynamic
diff --git a/testsuite/tests/plugins/Makefile b/testsuite/tests/plugins/Makefile
index d913ca5..f58a771 100644
--- a/testsuite/tests/plugins/Makefile
+++ b/testsuite/tests/plugins/Makefile
@@ -125,3 +125,8 @@ plugin-recomp-change-prof:
 .PHONY: T16104
 T16104:
 	"$(TEST_HC)" $(TEST_HC_OPTS) $(ghcPluginWayFlags) -v0 T16104.hs -package-db T16104-plugin/pkg.T16104-plugin/local.package.conf
+
+.PHONY: T16260
+T16260:
+	"$(TEST_HC)" $(TEST_HC_OPTS) $(ghcPluginWayFlags) -v0 T16260.hs -package-db simple-plugin/pkg.T16260/local.package.conf -fplugin Simple.TrustworthyPlugin
+	"$(TEST_HC)" $(TEST_HC_OPTS) $(ghcPluginWayFlags) -v0 T16260.hs -package-db simple-plugin/pkg.T16260/local.package.conf -fplugin Simple.TrustworthyPlugin -fplugin-trustworthy
diff --git a/testsuite/tests/plugins/T16260.hs b/testsuite/tests/plugins/T16260.hs
new file mode 100644
index 0000000..9c1b9b3
--- /dev/null
+++ b/testsuite/tests/plugins/T16260.hs
@@ -0,0 +1 @@
+module T16260 where
diff --git a/testsuite/tests/backpack/should_run/bkprun04.stdout b/testsuite/tests/plugins/T16260.stdout
similarity index 52%
copy from testsuite/tests/backpack/should_run/bkprun04.stdout
copy to testsuite/tests/plugins/T16260.stdout
index 91d6f80..ae9d3fb 100644
--- a/testsuite/tests/backpack/should_run/bkprun04.stdout
+++ b/testsuite/tests/plugins/T16260.stdout
@@ -1,2 +1,4 @@
 False
+None
 True
+Safe
diff --git a/testsuite/tests/plugins/all.T b/testsuite/tests/plugins/all.T
index 7570938..f53d9aa 100644
--- a/testsuite/tests/plugins/all.T
+++ b/testsuite/tests/plugins/all.T
@@ -215,3 +215,9 @@ test('T16104',
       pre_cmd('$MAKE -s --no-print-directory -C T16104-plugin package.T16104-plugin TOP={top}')
      ],
      makefile_test, [])
+
+test('T16260',
+     [extra_files(['simple-plugin/']),
+      pre_cmd('$MAKE -s --no-print-directory -C simple-plugin package.T16260 TOP={top}')
+      ],
+     makefile_test, [])
diff --git a/testsuite/tests/plugins/simple-plugin/Simple/TrustworthyPlugin.hs b/testsuite/tests/plugins/simple-plugin/Simple/TrustworthyPlugin.hs
new file mode 100644
index 0000000..c2b4568
--- /dev/null
+++ b/testsuite/tests/plugins/simple-plugin/Simple/TrustworthyPlugin.hs
@@ -0,0 +1,17 @@
+module Simple.TrustworthyPlugin (plugin) where
+
+import GhcPlugins
+import TcRnMonad
+
+plugin :: Plugin
+plugin = defaultPlugin
+  { renamedResultAction = keepRenamedSource
+  , typeCheckResultAction = printHaskellSafeMode
+  }
+  where
+    printHaskellSafeMode _ ms tcg = liftIO $ do
+      let dflags = ms_hspp_opts ms
+      safe <- finalSafeMode dflags tcg
+      print $ gopt Opt_PluginTrustworthy dflags
+      putStrLn $ showPpr dflags safe
+      return tcg
diff --git a/testsuite/tests/plugins/simple-plugin/simple-plugin.cabal b/testsuite/tests/plugins/simple-plugin/simple-plugin.cabal
index 0a3c49e..e6f3671 100644
--- a/testsuite/tests/plugins/simple-plugin/simple-plugin.cabal
+++ b/testsuite/tests/plugins/simple-plugin/simple-plugin.cabal
@@ -20,3 +20,4 @@ Library
         Simple.DataStructures
         Simple.SourcePlugin
         Simple.RemovePlugin
+        Simple.TrustworthyPlugin



More information about the ghc-commits mailing list