[project @ 2002-03-05 14:18:53 by simonmar]
[ghc-hetmet.git] / ghc / compiler / prelude / PrelInfo.lhs
index 168d04c..e97d288 100644 (file)
@@ -8,8 +8,10 @@ module PrelInfo (
        module PrelNames,
        module MkId,
 
-       wiredInNames,   -- Names of wired in things
-
+       wiredInThings,  -- Names of wired in things
+       wiredInThingEnv,
+       ghcPrimExports,
+       cCallableClassDecl, cReturnableClassDecl, assertDecl,
        
        -- Primop RdrNames
        eqH_Char_RDR,   ltH_Char_RDR,   eqH_Word_RDR,  ltH_Word_RDR, 
@@ -28,24 +30,26 @@ module PrelInfo (
 
 #include "HsVersions.h"
 
--- friends:
 import PrelNames       -- Prelude module names
 
-import PrimOp          ( PrimOp(..), allThePrimOps, primOpRdrName )
-import DataCon         ( DataCon, dataConId, dataConWrapId )
+import PrimOp          ( PrimOp(..), allThePrimOps, primOpRdrName, primOpOcc )
+import DataCon         ( DataCon )
+import Id              ( idName )
 import MkId            ( mkPrimOpId, wiredInIds )
 import MkId            -- All of it, for re-export
+import Name            ( nameOccName, nameRdrName )
+import RdrName         ( mkRdrUnqual )
+import HsSyn           ( HsTyVarBndr(..), TyClDecl(..), HsType(..) )
+import OccName         ( mkVarOcc )
 import TysPrim         ( primTyCons )
 import TysWiredIn      ( wiredInTyCons )
-
--- others:
-import RdrName         ( RdrName )
-import Name            ( Name, getName )
-import TyCon           ( tyConDataConsIfAvailable, TyCon )
+import RdrHsSyn                ( mkClassDecl )
+import HscTypes        ( TyThing(..), implicitTyThingIds, TypeEnv, mkTypeEnv,
+                         GenAvailInfo(..), RdrAvailInfo )
 import Class           ( Class, classKey )
-import Type            ( funTyCon )
-import Bag
-import BasicTypes      ( Boxity(..) )
+import Type            ( funTyCon, openTypeKind, liftedTypeKind )
+import TyCon           ( tyConName )
+import SrcLoc          ( noSrcLoc )
 import Util            ( isIn )
 \end{code}
 
@@ -59,36 +63,81 @@ We have two ``builtin name funs,'' one to look up @TyCons@ and
 @Classes@, the other to look up values.
 
 \begin{code}
-wiredInNames :: [Name]
-wiredInNames
-  = bagToList $ unionManyBags
-    [          -- Wired in TyCons
-         unionManyBags (map getTyConNames ([funTyCon] ++ primTyCons ++ wiredInTyCons))
+wiredInThings :: [TyThing]
+wiredInThings
+  = concat
+    [          -- Wired in TyCons and their implicit Ids
+         tycon_things
+       , map AnId (implicitTyThingIds tycon_things)
 
                -- Wired in Ids
-       , listToBag (map getName wiredInIds)
+       , map AnId wiredInIds
 
                -- PrimOps
-       , listToBag (map (getName . mkPrimOpId) allThePrimOps)
+       , map (AnId . mkPrimOpId) allThePrimOps
     ]
-\end{code}
-
+  where
+    tycon_things = map ATyCon ([funTyCon] ++ primTyCons ++ wiredInTyCons)
 
-\begin{code}
-getTyConNames :: TyCon -> Bag Name
-getTyConNames tycon
-    = getName tycon `consBag` 
-      unionManyBags (map get_data_con_names (tyConDataConsIfAvailable tycon))
-       -- Synonyms return empty list of constructors
-    where
-      get_data_con_names dc = listToBag [getName (dataConId dc),       -- Worker
-                                        getName (dataConWrapId dc)]    -- Wrapper
+wiredInThingEnv :: TypeEnv
+wiredInThingEnv = mkTypeEnv wiredInThings
 \end{code}
 
 We let a lot of "non-standard" values be visible, so that we can make
 sense of them in interface pragmas. It's cool, though they all have
 "non-standard" names, so they won't get past the parser in user code.
 
+%************************************************************************
+%*                                                                     *
+\subsection{Export lists for pseudo-modules (GHC.Prim)}
+%*                                                                     *
+%************************************************************************
+
+GHC.Prim "exports" all the primops and primitive types, some 
+wired-in Ids, and the CCallable & CReturnable classes.
+
+\begin{code}
+ghcPrimExports :: [RdrAvailInfo]
+ = AvailTC cCallableOcc [ cCallableOcc ] :
+   AvailTC cReturnableOcc [ cReturnableOcc ] :
+   Avail (nameOccName assertName) :    -- doesn't have an Id
+   map (Avail . nameOccName . idName) ghcPrimIds ++
+   map (Avail . primOpOcc) allThePrimOps ++
+   [ AvailTC occ [occ] |
+     n <- funTyCon : primTyCons, let occ = nameOccName (tyConName n) 
+   ]
+ where
+   cCallableOcc = nameOccName cCallableClassName
+   cReturnableOcc = nameOccName cReturnableClassName
+
+assertDecl
+  = IfaceSig { 
+       tcdName = nameRdrName assertName,
+       tcdType = HsForAllTy (Just [liftedAlpha]) [] (HsTyVar alpha),
+       tcdIdInfo = [],
+       tcdLoc = noSrcLoc
+    }
+
+cCallableClassDecl
+  = mkClassDecl
+    ([], nameRdrName cCallableClassName, [openAlpha])
+    [] -- no fds
+    [] -- no sigs
+    Nothing -- no mbinds
+    noSrcLoc
+
+cReturnableClassDecl
+  = mkClassDecl
+    ([], nameRdrName cReturnableClassName, [openAlpha])
+    [] -- no fds
+    [] -- no sigs
+    Nothing -- no mbinds
+    noSrcLoc
+
+alpha = mkRdrUnqual (mkVarOcc FSLIT("a"))
+openAlpha = IfaceTyVar alpha openTypeKind
+liftedAlpha = IfaceTyVar alpha liftedTypeKind
+\end{code}
 
 %************************************************************************
 %*                                                                     *