summaryrefslogtreecommitdiff
path: root/ghc/compiler/rename/RnMonad.lhs
diff options
context:
space:
mode:
authorsimonmar <unknown>2002-03-05 14:18:56 +0000
committersimonmar <unknown>2002-03-05 14:18:56 +0000
commitcaac75c6a454396dadff0323162ed14adb4893cd (patch)
tree2abe740fe26ab89f4605dad3ca760f6580b02bc0 /ghc/compiler/rename/RnMonad.lhs
parent027168af50b6eee2ee043caf7a030d490b40967e (diff)
downloadhaskell-caac75c6a454396dadff0323162ed14adb4893cd.tar.gz
[project @ 2002-03-05 14:18:53 by simonmar]
Generate the contents of the GHC.Prim interface file automatically from the list of available PrimOps and various other wired-in things. Two main benefits from this: - There's one fewer places to edit when adding a new primop. - It's one less reason to need the interface file parser, and now we no longer need the (short-lived) --compile-iface option so I've removed it.
Diffstat (limited to 'ghc/compiler/rename/RnMonad.lhs')
-rw-r--r--ghc/compiler/rename/RnMonad.lhs49
1 files changed, 36 insertions, 13 deletions
diff --git a/ghc/compiler/rename/RnMonad.lhs b/ghc/compiler/rename/RnMonad.lhs
index 5fff141b20..2eb8003edf 100644
--- a/ghc/compiler/rename/RnMonad.lhs
+++ b/ghc/compiler/rename/RnMonad.lhs
@@ -23,16 +23,6 @@ module RnMonad(
#include "HsVersions.h"
-#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 405
-import IOExts ( fixIO )
-#elif defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 302
-import PrelIOBase ( fixIO ) -- Should be in GlaExts
-#else
-import IOBase ( fixIO )
-#endif
-import IOExts ( IORef, newIORef, readIORef, writeIORef, unsafePerformIO )
-import IO ( hPutStr, stderr )
-
import HsSyn
import RdrHsSyn
import RnHsSyn ( RenamedFixitySig )
@@ -58,8 +48,13 @@ import Name ( Name, OccName, NamedThing(..),
nameOccName,
decode, mkLocalName, mkKnownKeyGlobal
)
-import NameEnv ( NameEnv, lookupNameEnv, emptyNameEnv, extendNameEnvList )
-import Module ( Module, ModuleName, ModuleSet, emptyModuleSet, PackageName )
+import NameEnv ( NameEnv, lookupNameEnv, emptyNameEnv,
+ extendNameEnvList )
+import Module ( Module, ModuleName, ModuleSet, emptyModuleSet,
+ PackageName )
+import PrelInfo ( ghcPrimExports,
+ cCallableClassDecl, cReturnableClassDecl, assertDecl )
+import PrelNames ( mkUnboundName, gHC_PRIM_Name )
import NameSet
import CmdLineOpts ( DynFlags, DynFlag(..), dopt )
import SrcLoc ( SrcLoc, generatedSrcLoc, noSrcLoc )
@@ -69,8 +64,11 @@ import Maybes ( seqMaybe )
import Bag ( Bag, emptyBag, isEmptyBag, snocBag )
import UniqSupply
import Outputable
-import PrelNames ( mkUnboundName )
+import IOExts ( IORef, newIORef, readIORef, writeIORef,
+ fixIO, unsafePerformIO )
+import IO ( hPutStr, stderr )
+
infixr 9 `thenRn`, `thenRn_`
\end{code}
@@ -232,6 +230,31 @@ data ParsedIface
%************************************************************************
%* *
+\subsection{Wired-in interfaces}
+%* *
+%************************************************************************
+
+\begin{code}
+ghcPrimIface :: ParsedIface
+ghcPrimIface = ParsedIface {
+ pi_mod = gHC_PRIM_Name,
+ pi_pkg = FSLIT("base"),
+ pi_vers = 1,
+ pi_orphan = False,
+ pi_usages = [],
+ pi_exports = (1, [(gHC_PRIM_Name, ghcPrimExports)]),
+ pi_decls = [(1,cCallableClassDecl),
+ (1,cReturnableClassDecl),
+ (1,assertDecl)],
+ pi_fixity = [],
+ pi_insts = [],
+ pi_rules = (1,[]),
+ pi_deprecs = Nothing
+ }
+\end{code}
+
+%************************************************************************
+%* *
\subsection{The renamer state}
%* *
%************************************************************************