Skip to content
Snippets Groups Projects
Commit 5295316c authored by sof's avatar sof
Browse files

[project @ 1997-09-04 20:19:15 by sof]

ppr wibble; new functions: dumpIfSet, doIfSet
parent d46d9882
Branches wip/T19847
No related tags found
No related merge requests found
......@@ -12,14 +12,15 @@ module ErrUtils (
addShortErrLocLine, addShortWarnLocLine,
dontAddErrLoc,
pprBagOfErrors,
ghcExit
ghcExit,
doIfSet, dumpIfSet
) where
IMP_Ubiq(){-uitous-}
import CmdLineOpts ( opt_PprUserLength )
import Bag --( bagToList )
import Outputable ( PprStyle(..), Outputable(..) )
import Outputable ( PprStyle(..), Outputable(..), printErrs )
import Pretty
import SrcLoc ( noSrcLoc, SrcLoc{-instance-} )
\end{code}
......@@ -53,7 +54,8 @@ dontAddErrLoc title rest_of_err_msg sty
pprBagOfErrors :: PprStyle -> Bag Error -> Doc
pprBagOfErrors sty bag_of_errors
= let pretties = map ( \ e -> e sty ) (bagToList bag_of_errors) in
= let pretties = map ( \ e -> e sty ) (bagToList bag_of_errors)
in
vcat (map (\ p -> ($$) space p) pretties)
\end{code}
......@@ -65,3 +67,23 @@ ghcExit val
then error "Compilation had errors\n"
else return ()
\end{code}
\begin{code}
doIfSet :: Bool -> IO () -> IO ()
doIfSet flag action | flag = action
| otherwise = return ()
\end{code}
\begin{code}
dumpIfSet :: Bool -> String -> Doc -> IO ()
dumpIfSet flag hdr doc
| not flag = return ()
| otherwise = printErrs dump
where
dump = (line <+> text hdr <+> line)
$$
doc
$$
text ""
line = text (take 20 (repeat '='))
\end{code}
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment