[commit: ghc] master: Replace `showSDocUnsafe` with `showSDoc` in extending_ghc.rst (d24e73a)
git at git.haskell.org
git at git.haskell.org
Thu Jun 14 14:07:14 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/d24e73adf7fb33e2c94b7b6c43fe9feb9b23c3a6/ghc
>---------------------------------------------------------------
commit d24e73adf7fb33e2c94b7b6c43fe9feb9b23c3a6
Author: HE, Tao <sighingnow at gmail.com>
Date: Thu Jun 14 09:18:49 2018 -0400
Replace `showSDocUnsafe` with `showSDoc` in extending_ghc.rst
... and fix compile errors.
Replace the usage of `showSDocUnsafe` with `showSDoc dflags`
in example code in extending_ghc.rts.
This example contains several compile errors (missing import
and syntax error), this patch also fixes that.
Test Plan: [skip ci]
Reviewers: bgamari, mpickering
Reviewed By: mpickering
Subscribers: mpickering, rwbarton, thomie, carter
GHC Trac Issues: #15228
Differential Revision: https://phabricator.haskell.org/D4815
>---------------------------------------------------------------
d24e73adf7fb33e2c94b7b6c43fe9feb9b23c3a6
docs/users_guide/extending_ghc.rst | 21 +++++++++++++++------
1 file changed, 15 insertions(+), 6 deletions(-)
diff --git a/docs/users_guide/extending_ghc.rst b/docs/users_guide/extending_ghc.rst
index 97f2143..91034e6 100644
--- a/docs/users_guide/extending_ghc.rst
+++ b/docs/users_guide/extending_ghc.rst
@@ -725,11 +725,15 @@ displayed.
module SourcePlugin where
import Control.Monad.IO.Class
+ import DynFlags (getDynFlags)
import Plugins
import HscTypes
import TcRnTypes
import HsExtension
+ import HsDecls
import HsExpr
+ import HsImpExp
+ import Avail
import Outputable
import HsDoc
@@ -743,7 +747,8 @@ displayed.
parsedPlugin :: [CommandLineOption] -> ModSummary -> HsParsedModule -> Hsc HsParsedModule
parsedPlugin _ _ pm
- = do liftIO $ putStrLn $ "parsePlugin: \n" ++ (showSDocUnsafe $ ppr $ hpm_module pm)
+ = do dflags <- getDynFlags
+ liftIO $ putStrLn $ "parsePlugin: \n" ++ (showSDoc dflags $ ppr $ hpm_module pm)
return pm
renamedAction :: [CommandLineOption] -> ModSummary
@@ -751,22 +756,26 @@ displayed.
, Maybe [(LIE GhcRn, Avails)], Maybe LHsDocString )
-> TcM ()
renamedAction _ _ ( gr, _, _, _ )
- = liftIO $ putStrLn "typeCheckPlugin (rn): " ++ (showSDocUnsafe $ ppr gr)
+ = do dflags <- getDynFlags
+ liftIO $ putStrLn $ "typeCheckPlugin (rn): " ++ (showSDoc dflags $ ppr gr)
typecheckPlugin :: [CommandLineOption] -> ModSummary -> TcGblEnv -> TcM TcGblEnv
typecheckPlugin _ _ tc
- = do liftIO $ putStrLn $ "typeCheckPlugin (rn): \n" ++ (showSDocUnsafe $ ppr $ tcg_rn_decls tc)
- liftIO $ putStrLn $ "typeCheckPlugin (tc): \n" ++ (showSDocUnsafe $ ppr $ tcg_binds tc)
+ = do dflags <- getDynFlags
+ liftIO $ putStrLn $ "typeCheckPlugin (rn): \n" ++ (showSDoc dflags $ ppr $ tcg_rn_decls tc)
+ liftIO $ putStrLn $ "typeCheckPlugin (tc): \n" ++ (showSDoc dflags $ ppr $ tcg_binds tc)
return tc
metaPlugin :: [CommandLineOption] -> LHsExpr GhcTc -> TcM (LHsExpr GhcTc)
metaPlugin _ meta
- = do liftIO $ putStrLn $ "meta: " ++ (showSDocUnsafe $ ppr meta)
+ = do dflags <- getDynFlags
+ liftIO $ putStrLn $ "meta: " ++ (showSDoc dflags $ ppr meta)
return meta
interfaceLoadPlugin :: [CommandLineOption] -> ModIface -> IfM lcl ModIface
interfaceLoadPlugin _ iface
- = do liftIO $ putStrLn $ "interface loaded: " ++ (showSDocUnsafe $ ppr $ mi_module iface)
+ = do dflags <- getDynFlags
+ liftIO $ putStrLn $ "interface loaded: " ++ (showSDoc dflags $ ppr $ mi_module iface)
return iface
When you compile a simple module that contains Template Haskell splice
More information about the ghc-commits
mailing list