[project @ 2000-12-07 08:17:55 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / OccName.lhs
index 76cbbb0..805bdf5 100644 (file)
@@ -1,4 +1,4 @@
-
+%
 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
 %
 
@@ -8,18 +8,19 @@
 module OccName (
        -- The NameSpace type; abstact
        NameSpace, tcName, clsName, tcClsName, dataName, varName, ipName,
-       tvName, uvName, nameSpaceString, 
+       tvName, nameSpaceString, 
 
        -- The OccName type
        OccName,        -- Abstract, instance of Outputable
        pprOccName, 
 
-       mkSrcOccFS, mkSysOcc, mkSysOccFS, mkCCallOcc, mkSrcVarOcc, mkKindOccFS,
+       mkOccFS, mkSysOcc, mkSysOccFS, mkCCallOcc, mkVarOcc, mkKindOccFS,
        mkSuperDictSelOcc, mkDFunOcc, mkForeignExportOcc,
        mkDictOcc, mkIPOcc, mkWorkerOcc, mkMethodOcc, mkDefaultMethodOcc,
        mkDerivedTyConOcc, mkClassTyConOcc, mkClassDataConOcc, mkSpecOcc,
+       mkGenOcc1, mkGenOcc2, 
        
-       isSysOcc, isTvOcc, isUvOcc, isDataOcc, isDataSymOcc, isSymOcc, isIPOcc, isValOcc,
+       isSysOcc, isTvOcc, isDataOcc, isDataSymOcc, isSymOcc, isIPOcc, isValOcc,
 
        occNameFS, occNameString, occNameUserString, occNameSpace, occNameFlavour, 
        setOccNameSpace,
@@ -39,7 +40,7 @@ module OccName (
 
 #include "HsVersions.h"
 
-import Char    ( isDigit, isAlpha, isUpper, isLower, ISALPHANUM, ord, chr, digitToInt, intToDigit )
+import Char    ( isDigit, isUpper, isLower, ISALPHANUM, ord, chr, digitToInt )
 import Util    ( thenCmp )
 import FiniteMap ( FiniteMap, emptyFM, lookupFM, addToFM, elemFM )
 import Outputable
@@ -66,7 +67,12 @@ type EncodedString = String  -- Encoded form
 
 
 pprEncodedFS :: EncodedFS -> SDoc
-pprEncodedFS fs = ptext fs
+pprEncodedFS fs
+  = getPprStyle        $ \ sty ->
+    if userStyle sty
+       -- ptext (decodeFS fs) would needlessly pack the string again
+       then text (decode (_UNPK_ fs))
+        else ptext fs
 \end{code}
 
 %************************************************************************
@@ -80,7 +86,6 @@ data NameSpace = VarName      -- Variables
               | IPName         -- Implicit Parameters
               | 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 )
@@ -93,7 +98,6 @@ tcClsName = TcClsName         -- Not sure which!
 
 dataName = DataName
 tvName   = TvName
-uvName   = UvName
 varName  = VarName
 ipName   = IPName
 
@@ -103,7 +107,6 @@ nameSpaceString DataName  = "Data constructor"
 nameSpaceString VarName   = "Variable"
 nameSpaceString IPName    = "Implicit Param"
 nameSpaceString TvName    = "Type variable"
-nameSpaceString UvName    = "Usage variable"
 nameSpaceString TcClsName = "Type constructor or class"
 \end{code}
 
@@ -171,7 +174,7 @@ mkCCallOcc :: EncodedString -> OccName
 -- But then alreadyEncoded complains about the braces!
 mkCCallOcc str = OccName varName (_PK_ str)
 
--- Kind constructors get a speical function.  Uniquely, they are not encoded,
+-- Kind constructors get a special function.  Uniquely, they are not encoded,
 -- so that they have names like '*'.  This means that *even in interface files*
 -- we'll get kinds like (* -> (* -> *)).  We can't use mkSysOcc because it
 -- has an ASSERT that doesn't hold.
@@ -182,11 +185,11 @@ mkKindOccFS occ_sp fs = OccName occ_sp fs
 *Source-code* things are encoded.
 
 \begin{code}
-mkSrcOccFS :: NameSpace -> UserFS -> OccName
-mkSrcOccFS occ_sp fs = mkSysOccFS occ_sp (encodeFS fs)
+mkOccFS :: NameSpace -> UserFS -> OccName
+mkOccFS occ_sp fs = mkSysOccFS occ_sp (encodeFS fs)
 
-mkSrcVarOcc :: UserFS -> OccName
-mkSrcVarOcc fs = mkSysOccFS varName (encodeFS fs)
+mkVarOcc :: UserFS -> OccName
+mkVarOcc fs = mkSysOccFS varName (encodeFS fs)
 \end{code}
 
 
@@ -219,14 +222,11 @@ occNameFlavour (OccName sp _) = nameSpaceString sp
 \end{code}
 
 \begin{code}
-isTvOcc, isDataSymOcc, isSymOcc, isUvOcc :: OccName -> Bool
+isTvOcc, isDataSymOcc, isSymOcc :: OccName -> Bool
 
 isTvOcc (OccName TvName _) = True
 isTvOcc other              = False
 
-isUvOcc (OccName UvName _) = True
-isUvOcc other              = False
-
 isValOcc (OccName VarName  _) = True
 isValOcc (OccName DataName _) = True
 isValOcc other               = False
@@ -303,7 +303,8 @@ mkDictOcc      = mk_simple_deriv varName  "$d"
 mkIPOcc                   = mk_simple_deriv varName  "$i"
 mkSpecOcc         = mk_simple_deriv varName  "$s"
 mkForeignExportOcc = mk_simple_deriv varName  "$f"
-
+mkGenOcc1           = mk_simple_deriv varName  "$gfrom"      -- Generics
+mkGenOcc2           = mk_simple_deriv varName  "$gto"        -- Generics
 mk_simple_deriv sp px occ = mk_deriv sp px (occNameString occ)
 
 
@@ -325,17 +326,9 @@ mkSuperDictSelOcc index cls_occ
 
 \begin{code}
 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            -- "$fOrdMaybe"
 
-         -> OccName    -- "$fOrdMaybe3"
-
-mkDFunOcc string index
-  = mk_deriv VarName "$f" (show_index ++ string)
-  where
-    show_index | index == 0 = ""
-              | otherwise  = show index
+mkDFunOcc string = mk_deriv VarName "$f" string
 \end{code}
 
 We used to add a '$m' to indicate a method, but that gives rise to bad
@@ -433,8 +426,8 @@ The basic encoding scheme is this.
 * Most other printable characters translate to 'zx' or 'Zx' for some
        alphabetic character x
 
-* The others translate as 'zxdd' where 'dd' is exactly two hexadecimal
-       digits for the ord of the character
+* The others translate as 'znnnU' where 'nnn' is the decimal number
+        of the character
 
        Before          After
        --------------------------
@@ -448,8 +441,11 @@ The basic encoding scheme is this.
        fooZ            fooZZ   
        :+              Zczp
        ()              Z0T
-       (,,,,)          Z4T
-
+       (,,,,)          Z4T     5-tuple
+       (#,,,,#)        Z4H     unboxed 5-tuple
+               (NB: the number is one different to the number of 
+               elements.  No real reason except that () is a zero-tuple,
+               while (,) is a 2-tuple.)
 
 \begin{code}
 -- alreadyEncoded is used in ASSERTs to check for encoded
@@ -458,10 +454,11 @@ The basic encoding scheme is this.
 alreadyEncoded :: String -> Bool
 alreadyEncoded s = all ok s
                 where
-                  ok ' ' = True                -- This is a bit of a lie; if we really wanted spaces
-                                               -- in names we'd have to encode them.  But we do put
-                                               -- spaces in ccall "occurrences", and we don't want to
-                                               -- reject them here
+                  ok ' ' = True
+                       -- This is a bit of a lie; if we really wanted spaces
+                       -- in names we'd have to encode them.  But we do put
+                       -- spaces in ccall "occurrences", and we don't want to
+                       -- reject them here
                   ok ch  = ISALPHANUM ch
 
 alreadyEncodedFS :: FAST_STRING -> Bool
@@ -469,20 +466,23 @@ alreadyEncodedFS fs = alreadyEncoded (_UNPK_ fs)
 
 encode :: UserString -> EncodedString
 encode cs = case maybe_tuple cs of
-               Just n  -> 'Z' : show n ++ "T"          -- Tuples go to Z2T etc
+               Just n  -> n            -- Tuples go to Z2T etc
                Nothing -> go cs
          where
                go []     = []
                go (c:cs) = encode_ch c ++ go cs
 
--- ToDo: Unboxed tuples too, perhaps?
-maybe_tuple ('(' : cs) = check_tuple (0::Int) cs
-maybe_tuple other      = Nothing
+maybe_tuple ('(' : '#' : cs) = case count_commas (0::Int) cs of
+                                (n, '#' : ')' : cs) -> Just ('Z' : shows n "H")
+                                other               -> Nothing
+maybe_tuple ('(' : cs)       = case count_commas (0::Int) cs of
+                                (n, ')' : cs) -> Just ('Z' : shows n "T")
+                                other         -> Nothing
+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
+count_commas :: Int -> String -> (Int, String)
+count_commas n (',' : cs) = count_commas (n+1) cs
+count_commas n cs        = (n,cs)
 
 encodeFS :: UserFS -> EncodedFS
 encodeFS fast_str  | all unencodedChar str = fast_str
@@ -526,9 +526,7 @@ 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
+encode_ch c    = 'z' : shows (ord c) "U"
 \end{code}
 
 Decode is used for user printing.
@@ -571,14 +569,16 @@ 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
+-- Characters not having a specific code are coded as z224U
 decode_escape (c : rest)
   | isDigit c = go (digitToInt c) rest
   where
     go n (c : rest) | isDigit c = go (10*n + digitToInt c) rest
     go n ('T' : rest)          = '(' : replicate n ',' ++ ')' : decode rest
+    go n ('H' : rest)          = '(' : '#' : replicate n ',' ++ '#' : ')' : decode rest
+    go n ('U' : rest)           = chr n : decode rest
     go n other = pprPanic "decode_escape" (ppr n <+> text (c:rest))
 
 decode_escape (c : rest) = pprTrace "decode_escape" (char c) (decode rest)