[project @ 1996-04-25 16:31:20 by partain]
[ghc-hetmet.git] / ghc / compiler / main / ErrUtils.lhs
index 5146016..e50ded5 100644 (file)
@@ -3,25 +3,30 @@
 %
 \section[ErrsUtils]{Utilities for error reporting}
 
-This is an internal module---access to these functions is through
-@Errors@.
-
-DPH errors are in here, too.
-
 \begin{code}
 #include "HsVersions.h"
 
-module ErrUtils where
-
-import Bag             ( Bag, bagToList )
-import Outputable
-import Pretty          -- to pretty-print error messages
-import SrcLoc          ( mkUnknownSrcLoc, SrcLoc )
-import Util
+module ErrUtils (
+       Error(..), Warning(..), Message(..),
+       addErrLoc,
+       addShortErrLocLine,
+       dontAddErrLoc,
+       pprBagOfErrors,
+       ghcExit
+    ) where
+
+import Ubiq{-uitous-}
+
+import Bag             ( bagToList )
+import PprStyle                ( PprStyle(..) )
+import Pretty
+import SrcLoc          ( mkUnknownSrcLoc, SrcLoc{-instance-} )
 \end{code}
 
 \begin{code}
-type Error = PprStyle -> Pretty
+type Error   = PprStyle -> Pretty
+type Warning = PprStyle -> Pretty
+type Message = PprStyle -> Pretty
 
 addErrLoc :: SrcLoc -> String -> Error -> Error
 addErrLoc locn title rest_of_err_msg sty
@@ -44,18 +49,13 @@ pprBagOfErrors :: PprStyle -> Bag Error -> Pretty
 pprBagOfErrors sty bag_of_errors
   = let  pretties = map ( \ e -> e sty ) (bagToList bag_of_errors)  in
     ppAboves (map (\ p -> ppAbove ppSP p) pretties)
+\end{code}
+
+\begin{code}
+ghcExit :: Int -> IO ()
 
-#ifdef DPH
-addWarningLoc :: SrcLoc -> Error -> Error
-addWarningLoc locn rest_of_err_msg sty
-  = ppHang (ppBesides [ppStr "*** Warning *** ",
-                      ppr PprForUser locn,ppStr ": "])
-        4 (ppAbove (rest_of_err_msg sty)
-                   (ppSP))
-
-addWarning :: Error -> Error
-addWarning rest_of_err_msg sty
-  = ppBeside (ppStr "*** Warning *** : ")
-            (rest_of_err_msg sty)
-#endif {- Data Parallel Haskell -}
+ghcExit val
+  = if val /= 0
+    then error "Compilation had errors\n"
+    else return ()
 \end{code}