Skip to content

Commit

Permalink
[project @ 1997-09-04 20:21:37 by sof]
Browse files Browse the repository at this point in the history
ppr tidy up
  • Loading branch information
sof committed Sep 4, 1997
1 parent 72592f2 commit 0f55a79
Showing 1 changed file with 23 additions and 14 deletions.
37 changes: 23 additions & 14 deletions ghc/compiler/coreSyn/CoreLint.lhs
Expand Up @@ -13,7 +13,7 @@ module CoreLint (
IMP_Ubiq()
import CmdLineOpts ( opt_PprUserLength )
import CmdLineOpts ( opt_D_show_passes, opt_PprUserLength, opt_DoCoreLinting )
import CoreSyn
import Bag
Expand All @@ -30,7 +30,8 @@ import Maybes ( catMaybes )
import Name ( isLocallyDefined, getSrcLoc, Name{-instance NamedThing-},
NamedThing(..) )
import PprCore
import Outputable ( PprStyle(..), Outputable(..) )
import Outputable ( PprStyle(..), Outputable(..), pprErrorsStyle, printErrs )
import ErrUtils ( doIfSet, ghcExit )
import PprType ( GenType, GenTyVar, TyCon )
import Pretty
import PrimOp ( primOpType, PrimOp(..) )
Expand Down Expand Up @@ -86,25 +87,33 @@ Outstanding issues:
--

\begin{code}
lintCoreBindings
:: PprStyle -> String -> Bool -> [CoreBinding] -> [CoreBinding]
lintCoreBindings :: String -> Bool -> [CoreBinding] -> IO ()
lintCoreBindings sty whoDunnit spec_done binds
lintCoreBindings whoDunnit spec_done binds
| not opt_DoCoreLinting
= return ()
lintCoreBindings whoDunnit spec_done binds
= case (initL (lint_binds binds) spec_done) of
Nothing -> binds
Just msg ->
pprPanic "" (vcat [
text ("*** Core Lint Errors: in " ++ whoDunnit ++ " ***"),
msg sty,
ptext SLIT("*** Offending Program ***"),
vcat (map (pprCoreBinding sty) binds),
ptext SLIT("*** End of Offense ***")
])
Nothing -> doIfSet opt_D_show_passes
(hPutStr stderr ("*** Core Linted result of " ++ whoDunnit ++ "\n"))
Just bad_news -> printErrs (display bad_news) >>
ghcExit 1
where
lint_binds [] = returnL ()
lint_binds (bind:binds)
= lintCoreBinding bind `thenL` \binders ->
addInScopeVars binders (lint_binds binds)
display bad_news
= vcat [
text ("*** Core Lint Errors: in result of " ++ whoDunnit ++ " ***"),
bad_news pprErrorsStyle,
ptext SLIT("*** Offending Program ***"),
pprCoreBindings pprErrorsStyle binds,
ptext SLIT("*** End of Offense ***")
]
\end{code}

%************************************************************************
Expand Down

0 comments on commit 0f55a79

Please sign in to comment.