Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Glasgow Haskell Compiler
GHC
Commits
9d246714
Commit
9d246714
authored
Jun 11, 2012
by
Ian Lynagh
Browse files
Pass DynFlags down to hPrintDump
parent
310ded12
Changes
4
Hide whitespace changes
Inline
Side-by-side
compiler/main/DynFlags.hs
View file @
9d246714
...
...
@@ -976,7 +976,7 @@ defaultLogAction :: LogAction
defaultLogAction
dflags
severity
srcSpan
style
msg
=
case
severity
of
SevOutput
->
printSDoc
msg
style
SevDump
->
hPrintDump
stdout
msg
SevDump
->
hPrintDump
dflags
stdout
msg
SevInfo
->
printErrs
msg
style
SevFatal
->
printErrs
msg
style
_
->
do
hPutChar
stderr
'
\n
'
...
...
compiler/main/DynFlags.hs-boot
0 → 100644
View file @
9d246714
module
DynFlags
where
data
DynFlags
compiler/main/ErrUtils.lhs
View file @
9d246714
...
...
@@ -247,7 +247,7 @@ dumpSDoc dflags dflag hdr doc
writeIORef gdref (Set.insert fileName gd)
createDirectoryIfMissing True (takeDirectory fileName)
handle <- openFile fileName mode
hPrintDump handle doc
hPrintDump
dflags
handle doc
hClose handle
-- write the dump to stdout
...
...
compiler/utils/Outputable.lhs
View file @
9d246714
...
...
@@ -71,6 +71,7 @@ module Outputable (
pprDebugAndThen,
) where
import {-# SOURCE #-} DynFlags( DynFlags )
import {-# SOURCE #-} Module( Module, ModuleName, moduleName )
import {-# SOURCE #-} Name( Name, nameModule )
...
...
@@ -319,8 +320,8 @@ ifPprDebug d = SDoc $ \ctx ->
\end{code}
\begin{code}
hPrintDump :: Handle -> SDoc -> IO ()
hPrintDump h doc = do
hPrintDump ::
DynFlags ->
Handle -> SDoc -> IO ()
hPrintDump
_
h doc = do
Pretty.printDoc PageMode h
(runSDoc better_doc (initSDocContext defaultDumpStyle))
hFlush h
...
...
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment