[project @ 2000-11-10 15:12:50 by simonpj]
[ghc-hetmet.git] / ghc / compiler / coreSyn / CoreLint.lhs
index cacfee7..ccd3afa 100644 (file)
@@ -7,43 +7,40 @@
 module CoreLint (
        lintCoreBindings,
        lintUnfolding, 
-       beginPass, endPass, endPassWithRules
+       showPass, endPass, endPassWithRules
     ) where
 
 #include "HsVersions.h"
 
-import IO      ( hPutStr, hPutStrLn, stderr, stdout )
+import IO              ( hPutStr, hPutStrLn, stdout )
 
-import CmdLineOpts      ( opt_D_show_passes, opt_DoCoreLinting, opt_PprStyle_Debug )
 import CoreSyn
 import Rules            ( RuleBase, pprRuleBase )
 import CoreFVs         ( idFreeVars, mustHaveLocalBinding )
 import CoreUtils       ( exprOkForSpeculation, coreBindsSize, mkPiType )
 
 import Bag
-import Literal         ( Literal, literalType )
-import DataCon         ( DataCon, dataConRepType )
-import Id              ( isDeadBinder )
+import Literal         ( literalType )
+import DataCon         ( dataConRepType )
 import Var             ( Var, Id, TyVar, idType, tyVarKind, isTyVar, isId )
 import VarSet
 import Subst           ( mkTyVarSubst, substTy )
-import Name            ( isLocallyDefined, getSrcLoc )
+import Name            ( getSrcLoc )
 import PprCore
-import ErrUtils                ( doIfSet, dumpIfSet, ghcExit, Message, 
+import ErrUtils                ( doIfSet_dyn, dumpIfSet, ghcExit, Message, showPass,
                          ErrMsg, addErrLocHdrLine, pprBagOfErrors,
                           WarnMsg, pprBagOfWarnings)
-import PrimRep         ( PrimRep(..) )
-import SrcLoc          ( SrcLoc, noSrcLoc, isNoSrcLoc )
-import Type            ( Type, Kind, tyVarsOfType,
+import SrcLoc          ( SrcLoc, noSrcLoc )
+import Type            ( Type, tyVarsOfType,
                          splitFunTy_maybe, mkTyVarTy,
                          splitForAllTy_maybe, splitTyConApp_maybe,
                          isUnLiftedType, typeKind, 
                          isUnboxedTupleType,
                          hasMoreBoxityInfo
                        )
-import PprType         ( {- instance Outputable Type -} )
-import TyCon           ( TyCon, isPrimTyCon, tyConDataCons )
+import TyCon           ( isPrimTyCon )
 import BasicTypes      ( RecFlag(..), isNonRec )
+import CmdLineOpts
 import Maybe
 import Outputable
 
@@ -61,29 +58,21 @@ place for them.  They print out stuff before and after core passes,
 and do Core Lint when necessary.
 
 \begin{code}
-beginPass :: String -> IO ()
-beginPass pass_name
-  | opt_D_show_passes
-  = hPutStrLn stderr ("*** " ++ pass_name)
-  | otherwise
-  = return ()
-
-
-endPass :: String -> Bool -> [CoreBind] -> IO [CoreBind]
-endPass pass_name dump_flag binds
+endPass :: DynFlags -> String -> Bool -> [CoreBind] -> IO [CoreBind]
+endPass dflags pass_name dump_flag binds
   = do  
-        (binds, _) <- endPassWithRules pass_name dump_flag binds Nothing
+        (binds, _) <- endPassWithRules dflags pass_name dump_flag binds Nothing
         return binds
 
-endPassWithRules :: String -> Bool -> [CoreBind] -> Maybe RuleBase
+endPassWithRules :: DynFlags -> String -> Bool -> [CoreBind] -> Maybe RuleBase
                  -> IO ([CoreBind], Maybe RuleBase)
-endPassWithRules pass_name dump_flag binds rules
+endPassWithRules dflags pass_name dump_flag binds rules
   = do 
         -- ToDo: force the rules?
 
        -- Report result size if required
        -- This has the side effect of forcing the intermediate to be evaluated
-       if opt_D_show_passes then
+       if dopt Opt_D_show_passes dflags then
           hPutStrLn stdout ("    Result size = " ++ show (coreBindsSize binds))
         else
           return ()
@@ -95,7 +84,7 @@ endPassWithRules pass_name dump_flag binds rules
                                               Just rb -> pprRuleBase rb)
 
        -- Type check
-       lintCoreBindings pass_name binds
+       lintCoreBindings dflags pass_name binds
         -- ToDo: lint the rules
 
        return (binds, rules)
@@ -133,13 +122,13 @@ Outstanding issues:
     --   may well be happening...);
 
 \begin{code}
-lintCoreBindings :: String -> [CoreBind] -> IO ()
+lintCoreBindings :: DynFlags -> String -> [CoreBind] -> IO ()
 
-lintCoreBindings whoDunnit binds
-  | not opt_DoCoreLinting
+lintCoreBindings dflags whoDunnit binds
+  | not (dopt Opt_DoCoreLinting dflags)
   = return ()
 
-lintCoreBindings whoDunnit binds
+lintCoreBindings dflags whoDunnit binds
   = case (initL (lint_binds binds)) of
       (Nothing, Nothing)       -> done_lint
 
@@ -159,8 +148,8 @@ lintCoreBindings whoDunnit binds
                                  returnL ()
     lint_bind (NonRec bndr rhs) = lintSingleBinding NonRecursive (bndr,rhs)
 
-    done_lint = doIfSet opt_D_show_passes
-                       (hPutStr stderr ("*** Core Linted result of " ++ whoDunnit ++ "\n"))
+    done_lint = doIfSet_dyn dflags Opt_D_show_passes
+                       (hPutStr stdout ("*** Core Linted result of " ++ whoDunnit ++ "\n"))
     warn warnings
       = vcat [
                 text ("*** Core Lint Warnings: in result of " ++ whoDunnit ++ " ***"),
@@ -193,19 +182,20 @@ We use this to check all unfoldings that come in from interfaces
 (it is very painful to catch errors otherwise):
 
 \begin{code}
-lintUnfolding :: SrcLoc
+lintUnfolding :: DynFlags 
+             -> SrcLoc
              -> [Var]          -- Treat these as in scope
              -> CoreExpr
              -> (Maybe Message, Maybe Message)         -- (Nothing,_) => OK
 
-lintUnfolding locn vars expr
-  | not opt_DoCoreLinting
+lintUnfolding dflags locn vars expr
+  | not (dopt Opt_DoCoreLinting dflags)
   = (Nothing, Nothing)
 
   | otherwise
   = initL (addLoc (ImportedUnfolding locn) $
-            addInScopeVars vars             $
-            lintCoreExpr expr)
+          addInScopeVars vars             $
+          lintCoreExpr expr)
 \end{code}
 
 %************************************************************************
@@ -589,9 +579,7 @@ addErr errs_so_far msg locs
    context     | opt_PprStyle_Debug = vcat (reverse cxts) $$ cxt1
               | otherwise          = cxt1
  
-   mk_msg msg
-     | isNoSrcLoc loc = (loc, hang context 4 msg)
-     | otherwise      = addErrLocHdrLine loc context msg
+   mk_msg msg = addErrLocHdrLine loc context msg
 
 addLoc :: LintLocInfo -> LintM a -> LintM a
 addLoc extra_loc m loc scope errs warns