[project @ 1996-03-19 08:58:34 by partain]
[ghc-hetmet.git] / ghc / compiler / rename / RnMonad12.lhs
similarity index 83%
rename from ghc/compiler/rename/RenameMonad12.lhs
rename to ghc/compiler/rename/RnMonad12.lhs
index b60f293..bfb7814 100644 (file)
@@ -1,26 +1,25 @@
 %
-% (c) The GRASP/AQUA Project, Glasgow University, 1992-1995
+% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
 %
-\section[RenameMonad12]{The monad used by the renamer passes 1 and 2}
+\section[RnMonad12]{The monad used by the renamer passes 1 and 2}
 
 \begin{code}
 #include "HsVersions.h"
 
-module RenameMonad12 (
+module RnMonad12 (
        Rn12M(..),
        initRn12, thenRn12, returnRn12,
        mapRn12, zipWithRn12, foldrRn12,
-       addErrRn12, getModuleNameRn12, recoverQuietlyRn12,
+       addErrRn12, getModuleNameRn12, recoverQuietlyRn12
 
        -- and to make the interface self-sufficient...
-       Bag, Pretty(..), PprStyle, PrettyRep
     ) where
 
-import Bag
-import Errors
-import Outputable
-import Pretty          -- for type Pretty
-import Util            -- for pragmas only
+import Ubiq{-uitous-}
+
+import Bag             ( emptyBag, isEmptyBag, snocBag, Bag )
+import ErrUtils                ( Error(..) )
+import Pretty          ( Pretty(..) )
 
 infixr 9 `thenRn12`
 \end{code}
@@ -34,10 +33,8 @@ type Rn12M result
   -> Bag Error
   -> (result, Bag Error)
 
-#ifdef __GLASGOW_HASKELL__
 {-# INLINE thenRn12 #-}
 {-# INLINE returnRn12 #-}
-#endif
 
 initRn12 :: FAST_STRING{-module name-} -> Rn12M a -> (a, Bag Error)
 initRn12 mod action = action mod emptyBag
@@ -65,6 +62,8 @@ zipWithRn12 f (x:xs) (y:ys)
   = f x y              `thenRn12` \ r ->
     zipWithRn12 f xs ys `thenRn12` \ rs ->
     returnRn12 (r:rs)
+-- NB: zipWithRn12 behaves like zipWithEqual
+-- (requires equal-length lists)
 
 foldrRn12 :: (a -> b -> Rn12M b) -> b -> [a] -> Rn12M b