summaryrefslogtreecommitdiff
path: root/ghc
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2020-06-26 12:58:02 +0200
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-08-12 03:50:12 -0400
commitaccbc242e555822a2060091af7188ce6e9b0144e (patch)
tree641ced97452a46a0ff17f6754d2150e283c9b9ca /ghc
parentf1088b3f31ceddf918a319c97557fb1f08a9a387 (diff)
downloadhaskell-accbc242e555822a2060091af7188ce6e9b0144e.tar.gz
DynFlags: disentangle Outputable
- put panic related functions into GHC.Utils.Panic - put trace related functions using DynFlags in GHC.Driver.Ppr One step closer making Outputable fully independent of DynFlags. Bump haddock submodule
Diffstat (limited to 'ghc')
-rw-r--r--ghc/GHCi/Leak.hs1
-rw-r--r--ghc/GHCi/UI.hs6
-rw-r--r--ghc/GHCi/UI/Info.hs1
-rw-r--r--ghc/GHCi/UI/Monad.hs16
-rw-r--r--ghc/GHCi/UI/Tags.hs1
-rw-r--r--ghc/Main.hs1
6 files changed, 16 insertions, 10 deletions
diff --git a/ghc/GHCi/Leak.hs b/ghc/GHCi/Leak.hs
index e6a11cb9af..88c64ecc15 100644
--- a/ghc/GHCi/Leak.hs
+++ b/ghc/GHCi/Leak.hs
@@ -12,6 +12,7 @@ import GHC
import GHC.Ptr (Ptr (..))
import GHCi.Util
import GHC.Driver.Types
+import GHC.Driver.Ppr
import GHC.Utils.Outputable
import GHC.Platform (target32Bit)
import Prelude
diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs
index 7180bc71ac..7cef2dd423 100644
--- a/ghc/GHCi/UI.hs
+++ b/ghc/GHCi/UI.hs
@@ -42,6 +42,7 @@ import GHC.Runtime.Interpreter.Types
import GHCi.RemoteTypes
import GHCi.BreakArray
import GHC.Driver.Session as DynFlags
+import GHC.Driver.Ppr hiding (printForUser)
import GHC.Utils.Error hiding (traceCmd)
import GHC.Driver.Finder as Finder
import GHC.Driver.Monad ( modifySession )
@@ -69,7 +70,7 @@ import GHC.Types.SrcLoc as SrcLoc
import qualified GHC.Parser.Lexer as Lexer
import GHC.Data.StringBuffer
-import GHC.Utils.Outputable hiding ( printForUser )
+import GHC.Utils.Outputable
import GHC.Runtime.Loader ( initializePlugins )
@@ -3430,8 +3431,9 @@ completeBreakpoint = wrapCompleter spaces $ \w -> do -- #3000
-- Extract all bids from all top-level identifiers in scope.
bidsFromInscopes :: GhciMonad m => m [String]
bidsFromInscopes = do
+ dflags <- getDynFlags
rdrs <- GHC.getRdrNamesInScope
- inscopess <- mapM createInscope $ (showSDocUnsafe . ppr) <$> rdrs
+ inscopess <- mapM createInscope $ (showSDoc dflags . ppr) <$> rdrs
imods <- interpretedHomeMods
let topLevels = filter ((`elem` imods) . snd) $ concat inscopess
bidss <- mapM (addNestedDecls) topLevels
diff --git a/ghc/GHCi/UI/Info.hs b/ghc/GHCi/UI/Info.hs
index 2b035e4428..7466a28ce8 100644
--- a/ghc/GHCi/UI/Info.hs
+++ b/ghc/GHCi/UI/Info.hs
@@ -38,6 +38,7 @@ import GHC.Driver.Session (HasDynFlags(..))
import GHC.Data.FastString
import GHC
import GHC.Driver.Monad
+import GHC.Driver.Ppr
import GHC.Types.Name
import GHC.Types.Name.Set
import GHC.Utils.Outputable
diff --git a/ghc/GHCi/UI/Monad.hs b/ghc/GHCi/UI/Monad.hs
index 63f330d86c..8c5baeee90 100644
--- a/ghc/GHCi/UI/Monad.hs
+++ b/ghc/GHCi/UI/Monad.hs
@@ -38,8 +38,8 @@ module GHCi.UI.Monad (
import GHCi.UI.Info (ModInfo)
import qualified GHC
import GHC.Driver.Monad hiding (liftIO)
-import GHC.Utils.Outputable hiding (printForUser)
-import qualified GHC.Utils.Outputable as Outputable
+import GHC.Utils.Outputable
+import qualified GHC.Driver.Ppr as Ppr
import GHC.Types.Name.Occurrence
import GHC.Driver.Session
import GHC.Data.FastString
@@ -235,7 +235,7 @@ prettyLocations locs =
instance Outputable BreakLocation where
ppr loc = (ppr $ breakModule loc) <+> ppr (breakLoc loc) <+> pprEnaDisa <+>
if null (onBreakCmd loc)
- then Outputable.empty
+ then empty
else doubleQuotes (text (onBreakCmd loc))
where pprEnaDisa = case breakEnabled loc of
True -> text "enabled"
@@ -331,26 +331,26 @@ unsetOption opt
printForUserNeverQualify :: GhcMonad m => SDoc -> m ()
printForUserNeverQualify doc = do
dflags <- getDynFlags
- liftIO $ Outputable.printForUser dflags stdout neverQualify AllTheWay doc
+ liftIO $ Ppr.printForUser dflags stdout neverQualify AllTheWay doc
printForUserModInfo :: GhcMonad m => GHC.ModuleInfo -> SDoc -> m ()
printForUserModInfo info doc = do
dflags <- getDynFlags
mUnqual <- GHC.mkPrintUnqualifiedForModule info
unqual <- maybe GHC.getPrintUnqual return mUnqual
- liftIO $ Outputable.printForUser dflags stdout unqual AllTheWay doc
+ liftIO $ Ppr.printForUser dflags stdout unqual AllTheWay doc
printForUser :: GhcMonad m => SDoc -> m ()
printForUser doc = do
unqual <- GHC.getPrintUnqual
dflags <- getDynFlags
- liftIO $ Outputable.printForUser dflags stdout unqual AllTheWay doc
+ liftIO $ Ppr.printForUser dflags stdout unqual AllTheWay doc
printForUserPartWay :: GhcMonad m => SDoc -> m ()
printForUserPartWay doc = do
unqual <- GHC.getPrintUnqual
dflags <- getDynFlags
- liftIO $ Outputable.printForUser dflags stdout unqual Outputable.DefaultDepth doc
+ liftIO $ Ppr.printForUser dflags stdout unqual DefaultDepth doc
-- | Run a single Haskell expression
runStmt
@@ -438,7 +438,7 @@ runWithStats getAllocs action = do
printStats :: DynFlags -> ActionStats -> IO ()
printStats dflags ActionStats{actionAllocs = mallocs, actionElapsedTime = secs}
= do let secs_str = showFFloat (Just 2) secs
- putStrLn (showSDoc dflags (
+ putStrLn (Ppr.showSDoc dflags (
parens (text (secs_str "") <+> text "secs" <> comma <+>
case mallocs of
Nothing -> empty
diff --git a/ghc/GHCi/UI/Tags.hs b/ghc/GHCi/UI/Tags.hs
index 9f4dfa6e53..bc86f39766 100644
--- a/ghc/GHCi/UI/Tags.hs
+++ b/ghc/GHCi/UI/Tags.hs
@@ -31,6 +31,7 @@ import Data.List
import Data.Maybe
import Data.Ord
import GHC.Driver.Phases
+import GHC.Driver.Ppr
import GHC.Utils.Panic
import Prelude
import System.Directory
diff --git a/ghc/Main.hs b/ghc/Main.hs
index fa6608761d..06a26c45ae 100644
--- a/ghc/Main.hs
+++ b/ghc/Main.hs
@@ -51,6 +51,7 @@ import GHC.Unit.State ( pprUnits, pprUnitsSimple )
import GHC.Driver.Phases
import GHC.Types.Basic ( failed )
import GHC.Driver.Session hiding (WarnReason(..))
+import GHC.Driver.Ppr
import GHC.Utils.Error
import GHC.Data.FastString
import GHC.Utils.Outputable as Outputable