[project @ 1999-11-01 17:09:54 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / OccName.lhs
index a22c590..1720506 100644 (file)
@@ -6,19 +6,9 @@
 
 \begin{code}
 module OccName (
-       -- Modules
-       Module,         -- Abstract, instance of Outputable
-       mkSrcModule, mkSrcModuleFS, mkSysModuleFS, mkImportModuleFS, mkBootModule, mkIfaceModuleFS,
-       moduleString, moduleUserString, moduleIfaceFlavour,
-       pprModule, pprModuleSep, pprModuleBoot,
-
-       -- IfaceFlavour
-       IfaceFlavour,
-       hiFile, hiBootFile, bootFlavour,
-
        -- The NameSpace type; abstact
        NameSpace, tcName, clsName, tcClsName, dataName, varName, tvName,
-       nameSpaceString, 
+       uvName, nameSpaceString, 
 
        -- The OccName type
        OccName,        -- Abstract, instance of Outputable
@@ -27,9 +17,9 @@ module OccName (
        mkSrcOccFS, mkSysOcc, mkSysOccFS, mkSrcVarOcc, mkKindOccFS,
        mkSuperDictSelOcc, mkDFunOcc, mkForeignExportOcc,
        mkDictOcc, mkWorkerOcc, mkMethodOcc, mkDefaultMethodOcc,
-       mkClassTyConOcc, mkClassDataConOcc, mkSpecOcc,
+       mkDerivedTyConOcc, mkClassTyConOcc, mkClassDataConOcc, mkSpecOcc,
        
-       isTvOcc, isDataOcc, isDataSymOcc, isSymOcc,
+       isTvOcc, isUvOcc, isDataOcc, isDataSymOcc, isSymOcc,
 
        occNameFS, occNameString, occNameUserString, occNameSpace, occNameFlavour, 
        setOccNameSpace,
@@ -38,7 +28,7 @@ module OccName (
        TidyOccEnv, emptyTidyOccEnv, tidyOccName, initTidyOccEnv,
 
        -- Encoding
-       EncodedString, EncodedFS, UserString, UserFS, encode, encodeFS, decode,
+       EncodedString, EncodedFS, UserString, UserFS, encode, encodeFS, decode, pprEncodedFS,
 
        -- The basic form of names
        isLexCon, isLexVar, isLexId, isLexSym,
@@ -68,7 +58,7 @@ code the encoding operation is not performed on each occurrence.
 These type synonyms help documentation.
 
 \begin{code}
-type UserFS     = FAST_STRING  -- As the user typed it
+type UserFS    = FAST_STRING   -- As the user typed it
 type EncodedFS = FAST_STRING   -- Encoded form
 
 type UserString = String       -- As the user typed it
@@ -84,119 +74,6 @@ pprEncodedFS fs
        ptext fs
 \end{code}
 
-
-%************************************************************************
-%*                                                                     *
-\subsection{Interface file flavour}
-%*                                                                     *
-%************************************************************************
-
-The IfaceFlavour type is used mainly in an imported Name's Provenance
-to say whether the name comes from a regular .hi file, or whether it comes
-from a hand-written .hi-boot file.  This is important, because it has to be 
-propagated.  Suppose
-
-       C.hs imports B
-       B.hs imports A
-       A.hs imports C {-# SOURCE -#} ( f )
-
-Then in A.hi we may mention C.f, in an inlining.  When compiling B we *must not* 
-read C.f's details from C.hi, even if the latter happens to exist from an earlier
-compilation run.  So we use the name "C!f" in A.hi, and when looking for an interface
-file with details of C!f we look in C.hi-boot.  The "!" stuff is recorded in the
-IfaceFlavour in the Module of C.f in A. 
-
-Not particularly beautiful, but it works.
-
-\begin{code}
-data IfaceFlavour = HiFile             -- The thing comes from a standard interface file
-                                       -- or from the source file itself
-                 | HiBootFile          -- ... or from a handwritten "hi-boot" interface file
-                 deriving( Eq )
-
-hiFile     = HiFile
-hiBootFile = HiBootFile
-
-instance Text IfaceFlavour where       -- Just used in debug prints of lex tokens
-  showsPrec n HiFile     s = s
-  showsPrec n HiBootFile s = "!" ++ s
-
-bootFlavour :: IfaceFlavour -> Bool
-bootFlavour HiBootFile = True
-bootFlavour HiFile     = False
-\end{code}
-
-
-%************************************************************************
-%*                                                                     *
-\subsection[Module]{The name of a module}
-%*                                                                     *
-%************************************************************************
-
-\begin{code}
-data Module = Module
-               EncodedFS
-               IfaceFlavour
-       -- Haskell module names can include the quote character ',
-       -- so the module names have the z-encoding applied to them
-\end{code}
-
-\begin{code}
-instance Outputable Module where
-  ppr = pprModule
-
--- Ignore the IfaceFlavour when comparing modules
-instance Eq Module where
-  (Module m1 _) == (Module m2 _) = m1 == m2
-
-instance Ord Module where
-  (Module m1 _) `compare` (Module m2 _) = m1 `compare` m2
-\end{code}
-
-
-\begin{code}
-pprModule :: Module -> SDoc
-pprModule (Module mod _) = pprEncodedFS mod
-
-pprModuleSep, pprModuleBoot :: Module -> SDoc
-pprModuleSep (Module mod HiFile)     = dot
-pprModuleSep (Module mod HiBootFile) = char '!'
-
-pprModuleBoot (Module mod HiFile)     = empty
-pprModuleBoot (Module mod HiBootFile) = char '!'
-\end{code}
-
-
-\begin{code}
-mkSrcModule :: UserString -> Module
-mkSrcModule s = Module (_PK_ (encode s)) HiFile
-
-mkSrcModuleFS :: UserFS -> Module
-mkSrcModuleFS s = Module (encodeFS s) HiFile
-
-mkImportModuleFS :: UserFS -> IfaceFlavour -> Module
-mkImportModuleFS s hif = Module (encodeFS s) hif
-
-mkSysModuleFS :: EncodedFS -> IfaceFlavour -> Module
-mkSysModuleFS s hif = Module s hif
-
-mkIfaceModuleFS :: EncodedFS -> Module
-mkIfaceModuleFS s = Module s HiFile
-
-mkBootModule :: Module -> Module
-mkBootModule (Module s _) = Module s HiBootFile
-
-moduleString :: Module -> EncodedString
-moduleString (Module mod _) = _UNPK_ mod
-
-moduleUserString :: Module -> UserString
-moduleUserString (Module mod _) = decode (_UNPK_ mod)
-
-moduleIfaceFlavour :: Module -> IfaceFlavour
-moduleIfaceFlavour (Module _ hif) = hif
-\end{code}
-
-
 %************************************************************************
 %*                                                                     *
 \subsection{Name space}
@@ -207,6 +84,7 @@ moduleIfaceFlavour (Module _ hif) = hif
 data NameSpace = VarName       -- Variables
               | DataName       -- Data constructors
               | TvName         -- Type variables
+              | UvName         -- Usage variables
               | TcClsName      -- Type constructors and classes; Haskell has them
                                -- in the same name space for now.  
               deriving( Eq, Ord )
@@ -219,6 +97,7 @@ tcClsName = TcClsName                -- Not sure which!
 
 dataName = DataName
 tvName   = TvName
+uvName   = UvName
 varName  = VarName
 
 
@@ -226,6 +105,7 @@ nameSpaceString :: NameSpace -> String
 nameSpaceString DataName  = "Data constructor"
 nameSpaceString VarName   = "Variable"
 nameSpaceString TvName    = "Type variable"
+nameSpaceString UvName    = "Usage variable"
 nameSpaceString TcClsName = "Type constructor or class"
 \end{code}
 
@@ -334,11 +214,14 @@ occNameFlavour (OccName sp _) = nameSpaceString sp
 \end{code}
 
 \begin{code}
-isTvOcc, isDataSymOcc, isSymOcc :: OccName -> Bool
+isTvOcc, isDataSymOcc, isSymOcc, isUvOcc :: OccName -> Bool
 
 isTvOcc (OccName TvName _) = True
 isTvOcc other              = False
 
+isUvOcc (OccName UvName _) = True
+isUvOcc other              = False
+
 -- Data constructor operator (starts with ':', or '[]')
 -- Pretty inefficient!
 isDataSymOcc (OccName DataName s) = isLexConSym (decodeFS s)
@@ -366,7 +249,7 @@ Here's our convention for splitting up the interface file name space:
                        (local variables, so no name-clash worries)
 
        $f...           dict-fun identifiers (from inst decls)
-       $m...           default methods
+       $dm...          default methods
        $p...           superclass selectors
        $w...           workers
        $T...           compiler-generated tycons for dictionaries
@@ -401,8 +284,9 @@ mkDictOcc, mkWorkerOcc, mkDefaultMethodOcc,
 -- These derived variables have a prefix that no Haskell value could have
 mkWorkerOcc        = mk_simple_deriv varName  "$w"
 mkDefaultMethodOcc = mk_simple_deriv varName  "$dm"
-mkClassTyConOcc    = mk_simple_deriv tcName   ":T"     -- The : prefix makes sure it classifies
-mkClassDataConOcc  = mk_simple_deriv dataName ":D"     -- as a tycon/datacon
+mkDerivedTyConOcc  = mk_simple_deriv tcName   ":"      -- The : prefix makes sure it classifies
+mkClassTyConOcc    = mk_simple_deriv tcName   ":T"     -- as a tycon/datacon
+mkClassDataConOcc  = mk_simple_deriv dataName ":D"     --
 mkDictOcc         = mk_simple_deriv varName  "$d"
 mkSpecOcc         = mk_simple_deriv varName  "$s"
 mkForeignExportOcc = mk_simple_deriv varName  "$f"
@@ -420,18 +304,16 @@ mkSuperDictSelOcc index cls_occ
 
 
 \begin{code}
-mkDFunOcc :: OccName   -- class, eg "Ord"
-         -> OccName    -- tycon (or something convenient from the instance type)
-                       --      eg "Maybe"
-         -> Int        -- Unique to distinguish dfuns which share the previous two
-                       --      eg 3
-         -> OccName    -- "dOrdMaybe3"
-
-mkDFunOcc cls_occ tycon_occ index
-  = mk_deriv VarName "$f" (show_index ++ cls_str ++ tycon_str)
+mkDFunOcc :: EncodedString     -- Typically the class and type glommed together e.g. "OrdMaybe"
+         -> Int                -- Unique to distinguish dfuns which share the previous two
+                               --      eg 3
+         -- The requirement is that the (string,index) pair be unique in this module
+
+         -> OccName    -- "$fOrdMaybe3"
+
+mkDFunOcc string index
+  = mk_deriv VarName "$f" (show_index ++ string)
   where
-    cls_str   = occNameString cls_occ
-    tycon_str = occNameString tycon_occ
     show_index | index == 0 = ""
               | otherwise  = show index
 \end{code}
@@ -571,9 +453,10 @@ encode cs = case maybe_tuple cs of
                go (c:cs) = encode_ch c ++ go cs
 
 -- ToDo: Unboxed tuples too, perhaps?
-maybe_tuple ('(' : cs) = check_tuple 0 cs
+maybe_tuple ('(' : cs) = check_tuple (0::Int) cs
 maybe_tuple other      = Nothing
 
+check_tuple :: Int -> String -> Maybe Int
 check_tuple n (',' : cs) = check_tuple (n+1) cs
 check_tuple n ")"       = Just n
 check_tuple n other      = Nothing
@@ -618,6 +501,8 @@ encode_ch '\'' = "zq"
 encode_ch '\\' = "zr"
 encode_ch '/'  = "zs"
 encode_ch '*'  = "zt"
+encode_ch '^'  = "zu"
+encode_ch '%'  = "zv"
 encode_ch c    = ['z', 'x', intToDigit hi, intToDigit lo]
               where
                 (hi,lo) = ord c `quotRem` 16
@@ -660,6 +545,8 @@ decode_escape ('q' : rest) = '\'' : decode rest
 decode_escape ('r' : rest) = '\\' : decode rest
 decode_escape ('s' : rest) = '/' : decode rest
 decode_escape ('t' : rest) = '*' : decode rest
+decode_escape ('u' : rest) = '^' : decode rest
+decode_escape ('v' : rest) = '%' : decode rest
 decode_escape ('x' : d1 : d2 : rest) = chr (digitToInt d1 * 16 + digitToInt d2)  : decode rest
 
 -- Tuples are coded as Z23T