X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FbasicTypes%2FOccName.lhs;h=3cc7372ad628c2364131efec383defd698499226;hb=89cb459ac5c7b1606f835f0170bd08decb1ef795;hp=5b1ed1851615c43fd241d8091f7319597d238fdf;hpb=111cee3f1ad93816cb828e38b38521d85c3bcebb;p=ghc-hetmet.git diff --git a/ghc/compiler/basicTypes/OccName.lhs b/ghc/compiler/basicTypes/OccName.lhs index 5b1ed18..3cc7372 100644 --- a/ghc/compiler/basicTypes/OccName.lhs +++ b/ghc/compiler/basicTypes/OccName.lhs @@ -1,4 +1,4 @@ - +% % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % @@ -7,19 +7,20 @@ \begin{code} module OccName ( -- The NameSpace type; abstact - NameSpace, tcName, clsName, tcClsName, dataName, varName, ipName, - tvName, uvName, nameSpaceString, + NameSpace, tcName, clsName, tcClsName, dataName, varName, + tvName, nameSpaceString, -- The OccName type OccName, -- Abstract, instance of Outputable pprOccName, - mkSrcOccFS, mkSysOcc, mkSysOccFS, mkCCallOcc, mkSrcVarOcc, mkKindOccFS, + mkOccFS, mkSysOcc, mkSysOccFS, mkFCallOcc, mkVarOcc, mkKindOccFS, mkSuperDictSelOcc, mkDFunOcc, mkForeignExportOcc, mkDictOcc, mkIPOcc, mkWorkerOcc, mkMethodOcc, mkDefaultMethodOcc, mkDerivedTyConOcc, mkClassTyConOcc, mkClassDataConOcc, mkSpecOcc, + mkGenOcc1, mkGenOcc2, - isTvOcc, isUvOcc, isDataOcc, isDataSymOcc, isSymOcc, isIPOcc, isValOcc, + isTvOcc, isDataOcc, isDataSymOcc, isSymOcc, 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 @@ -68,10 +69,10 @@ type EncodedString = String -- Encoded form pprEncodedFS :: EncodedFS -> SDoc pprEncodedFS fs = getPprStyle $ \ sty -> - if userStyle sty then - text (decode (_UNPK_ fs)) - else - ptext fs + if userStyle sty + -- ptext (decodeFS fs) would needlessly pack the string again + then text (decode (_UNPK_ fs)) + else ptext fs \end{code} %************************************************************************ @@ -82,10 +83,8 @@ pprEncodedFS fs \begin{code} 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 ) @@ -98,17 +97,13 @@ tcClsName = TcClsName -- Not sure which! dataName = DataName tvName = TvName -uvName = UvName varName = VarName -ipName = IPName nameSpaceString :: NameSpace -> String 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} @@ -169,14 +164,14 @@ mkSysOccFS :: NameSpace -> EncodedFS -> OccName mkSysOccFS occ_sp fs = ASSERT2( alreadyEncodedFS fs, ppr fs ) OccName occ_sp fs -mkCCallOcc :: EncodedString -> OccName +mkFCallOcc :: EncodedString -> OccName -- This version of mkSysOcc doesn't check that the string is already encoded, -- because it will be something like "{__ccall f dyn Int# -> Int#}" -- This encodes a lot into something that then parses like an Id. -- But then alreadyEncoded complains about the braces! -mkCCallOcc str = OccName varName (_PK_ str) +mkFCallOcc 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. @@ -187,11 +182,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} @@ -224,14 +219,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 @@ -248,9 +240,6 @@ isDataOcc other = False -- Pretty inefficient! isSymOcc (OccName DataName s) = isLexConSym (decodeFS s) isSymOcc (OccName VarName s) = isLexSym (decodeFS s) - -isIPOcc (OccName IPName _) = True -isIPOcc _ = False \end{code} @@ -308,7 +297,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) \end{code} @@ -323,17 +313,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 @@ -422,32 +404,35 @@ The basic encoding scheme is this. * Tuples (,,,) are coded as Z3T -* Alphabetic characters (upper and lower), digits, and '_' +* Alphabetic characters (upper and lower) and digits all translate to themselves; except 'Z', which translates to 'ZZ' and 'z', which translates to 'zz' We need both so that we can preserve the variable/tycon distinction -* Most other printable characters translate to 'Zx' for some +* 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 -------------------------- Trak Trak - foo_wib foo_wib - > Zg - >1 Zg1 - foo# fooZh - foo## fooZhZh - foo##1 fooZhXh1 + foo_wib foozuwib + > zg + >1 zg1 + foo# foozh + foo## foozhzh + foo##1 foozhzh1 fooZ fooZZ - :+ ZcZp + :+ 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 @@ -456,11 +441,11 @@ The basic encoding scheme is this. alreadyEncoded :: String -> Bool alreadyEncoded s = all ok s where - ok '_' = True - 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 @@ -468,20 +453,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 @@ -490,7 +478,6 @@ encodeFS fast_str | all unencodedChar str = fast_str str = _UNPK_ fast_str unencodedChar :: Char -> Bool -- True for chars that don't need encoding -unencodedChar '_' = True unencodedChar 'Z' = False unencodedChar 'z' = False unencodedChar c = ISALPHANUM c @@ -510,6 +497,7 @@ encode_ch 'Z' = "ZZ" encode_ch 'z' = "zz" encode_ch '&' = "za" encode_ch '|' = "zb" +encode_ch '^' = "zc" encode_ch '$' = "zd" encode_ch '=' = "ze" encode_ch '>' = "zg" @@ -523,11 +511,9 @@ encode_ch '\'' = "zq" encode_ch '\\' = "zr" encode_ch '/' = "zs" encode_ch '*' = "zt" -encode_ch '^' = "zu" +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. @@ -544,16 +530,17 @@ decode (c : rest) = c : decode rest decode_escape :: EncodedString -> UserString -decode_escape ('Z' : rest) = 'Z' : decode rest -decode_escape ('C' : rest) = ':' : decode rest decode_escape ('L' : rest) = '(' : decode rest decode_escape ('R' : rest) = ')' : decode rest decode_escape ('M' : rest) = '[' : decode rest decode_escape ('N' : rest) = ']' : decode rest +decode_escape ('C' : rest) = ':' : decode rest +decode_escape ('Z' : rest) = 'Z' : decode rest decode_escape ('z' : rest) = 'z' : decode rest decode_escape ('a' : rest) = '&' : decode rest decode_escape ('b' : rest) = '|' : decode rest +decode_escape ('c' : rest) = '^' : decode rest decode_escape ('d' : rest) = '$' : decode rest decode_escape ('e' : rest) = '=' : decode rest decode_escape ('g' : rest) = '>' : decode rest @@ -567,16 +554,18 @@ 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 ('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) @@ -607,32 +596,29 @@ isLexSym cs = isLexConSym cs || isLexVarSym cs isLexConId cs -- Prefix type or data constructors | _NULL_ cs = False -- e.g. "Foo", "[]", "(,)" | cs == SLIT("[]") = True - | c == '(' = True -- (), (,), (,,), ... - | otherwise = isUpper c || isUpperISO c - where - c = _HEAD_ cs + | otherwise = startsConId (_HEAD_ cs) isLexVarId cs -- Ordinary prefix identifiers | _NULL_ cs = False -- e.g. "x", "_x" - | otherwise = isLower c || isLowerISO c || c == '_' - where - c = _HEAD_ cs + | otherwise = startsVarId (_HEAD_ cs) isLexConSym cs -- Infix type or data constructors | _NULL_ cs = False -- e.g. ":-:", ":", "->" - | otherwise = c == ':' - || cs == SLIT("->") - where - c = _HEAD_ cs + | cs == SLIT("->") = True + | otherwise = startsConSym (_HEAD_ cs) isLexVarSym cs -- Infix identifiers | _NULL_ cs = False -- e.g. "+" - | otherwise = isSymbolASCII c - || isSymbolISO c - where - c = _HEAD_ cs + | otherwise = startsVarSym (_HEAD_ cs) ------------- +startsVarSym, startsVarId, startsConSym, startsConId :: Char -> Bool +startsVarSym c = isSymbolASCII c || isSymbolISO c -- Infix Ids +startsConSym c = c == ':' -- Infix data constructors +startsVarId c = isLower c || isLowerISO c || c == '_' -- Ordinary Ids +startsConId c = isUpper c || isUpperISO c || c == '(' -- Ordinary type constructors and data constructors + + isSymbolASCII c = c `elem` "!#$%&*+./<=>?@\\^|~-" isSymbolISO c = ord c `elem` (0xd7 : 0xf7 : [0xa1 .. 0xbf]) isUpperISO (C# c#) = c# `geChar#` '\xc0'# && c# `leChar#` '\xde'# && c# `neChar#` '\xd7'#