X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FbasicTypes%2FOccName.lhs;h=76cbbb06c50c322afe3fda619835f2861f5d9c3d;hb=3c1b89ab88b2f349a698e9eb05d0e971a670f245;hp=cba9b4fb894c68f75b1b3160c2d607a4166138f4;hpb=18976e614fd90a8d81ced2c3e9cd8e38d72a1f40;p=ghc-hetmet.git diff --git a/ghc/compiler/basicTypes/OccName.lhs b/ghc/compiler/basicTypes/OccName.lhs index cba9b4f..76cbbb0 100644 --- a/ghc/compiler/basicTypes/OccName.lhs +++ b/ghc/compiler/basicTypes/OccName.lhs @@ -6,30 +6,20 @@ \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, + NameSpace, tcName, clsName, tcClsName, dataName, varName, ipName, + tvName, uvName, nameSpaceString, -- The OccName type OccName, -- Abstract, instance of Outputable pprOccName, - mkSrcOccFS, mkSysOcc, mkSysOccFS, mkSrcVarOcc, mkKindOccFS, + mkSrcOccFS, mkSysOcc, mkSysOccFS, mkCCallOcc, mkSrcVarOcc, mkKindOccFS, mkSuperDictSelOcc, mkDFunOcc, mkForeignExportOcc, - mkDictOcc, mkWorkerOcc, mkMethodOcc, mkDefaultMethodOcc, - mkClassTyConOcc, mkClassDataConOcc, mkSpecOcc, + mkDictOcc, mkIPOcc, mkWorkerOcc, mkMethodOcc, mkDefaultMethodOcc, + mkDerivedTyConOcc, mkClassTyConOcc, mkClassDataConOcc, mkSpecOcc, - isTvOcc, isDataOcc, isDataSymOcc, isSymOcc, + isSysOcc, isTvOcc, isUvOcc, isDataOcc, isDataSymOcc, isSymOcc, isIPOcc, isValOcc, 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 @@ -76,127 +66,9 @@ type EncodedString = String -- Encoded form pprEncodedFS :: EncodedFS -> SDoc -pprEncodedFS fs - = getPprStyle $ \ sty -> - if userStyle sty then - text (decode (_UNPK_ fs)) - else - 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 '!' +pprEncodedFS fs = ptext fs \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} @@ -205,10 +77,12 @@ moduleIfaceFlavour (Module _ hif) = hif \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. + -- in the same name space for now. deriving( Eq, Ord ) -- Though type constructors and classes are in the same name space now, @@ -219,13 +93,17 @@ 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} @@ -279,13 +157,20 @@ already encoded \begin{code} mkSysOcc :: NameSpace -> EncodedString -> OccName -mkSysOcc occ_sp str = ASSERT( alreadyEncoded str ) +mkSysOcc occ_sp str = ASSERT2( alreadyEncoded str, text str ) OccName occ_sp (_PK_ str) mkSysOccFS :: NameSpace -> EncodedFS -> OccName mkSysOccFS occ_sp fs = ASSERT2( alreadyEncodedFS fs, ppr fs ) OccName occ_sp fs +mkCCallOcc :: 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) + -- Kind constructors get a speical 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 @@ -334,23 +219,33 @@ 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 + +isValOcc (OccName VarName _) = True +isValOcc (OccName DataName _) = True +isValOcc other = False + -- Data constructor operator (starts with ':', or '[]') -- Pretty inefficient! isDataSymOcc (OccName DataName s) = isLexConSym (decodeFS s) isDataSymOcc other = False isDataOcc (OccName DataName _) = True -isDataOcc oter = False +isDataOcc other = False -- Any operator (data constructor or variable) -- Pretty inefficient! isSymOcc (OccName DataName s) = isLexConSym (decodeFS s) isSymOcc (OccName VarName s) = isLexSym (decodeFS s) + +isIPOcc (OccName IPName _) = True +isIPOcc _ = False \end{code} @@ -366,7 +261,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 @@ -394,21 +289,29 @@ mk_deriv occ_sp sys_prefix str = mkSysOcc occ_sp (encode sys_prefix ++ str) \end{code} \begin{code} -mkDictOcc, mkWorkerOcc, mkMethodOcc, mkDefaultMethodOcc, +mkDictOcc, mkIPOcc, mkWorkerOcc, mkDefaultMethodOcc, mkClassTyConOcc, mkClassDataConOcc, mkSpecOcc :: OccName -> OccName -- These derived variables have a prefix that no Haskell value could have mkWorkerOcc = mk_simple_deriv varName "$w" -mkMethodOcc = mk_simple_deriv varName "$m" 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" +mkIPOcc = mk_simple_deriv varName "$i" mkSpecOcc = mk_simple_deriv varName "$s" mkForeignExportOcc = mk_simple_deriv varName "$f" mk_simple_deriv sp px occ = mk_deriv sp px (occNameString occ) + + +isSysOcc :: OccName -> Bool -- True for all these '$' things +isSysOcc occ = case occNameUserString occ of + ('$' : _ ) -> True + other -> False -- We don't care about the ':' ones + -- isSysOcc is only called for Ids anyway \end{code} \begin{code} @@ -421,22 +324,45 @@ 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} +We used to add a '$m' to indicate a method, but that gives rise to bad +error messages from the type checker when we print the function name or pattern +of an instance-decl binding. Why? Because the binding is zapped +to use the method name in place of the selector name. +(See TcClassDcl.tcMethodBind) + +The way it is now, -ddump-xx output may look confusing, but +you can always say -dppr-debug to get the uniques. + +However, we *do* have to zap the first character to be lower case, +because overloaded constructors (blarg) generate methods too. +And convert to VarName space + +e.g. a call to constructor MkFoo where + data (Ord a) => Foo a = MkFoo a + +If this is necessary, we do it by prefixing '$m'. These +guys never show up in error messages. What a hack. + +\begin{code} +mkMethodOcc :: OccName -> OccName +mkMethodOcc occ@(OccName VarName fs) = occ +mkMethodOcc occ = mk_simple_deriv varName "$m" occ +\end{code} + %************************************************************************ %* * @@ -498,29 +424,29 @@ 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 +* The others translate as 'zxdd' where 'dd' is exactly two hexadecimal digits for the ord 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 @@ -532,7 +458,10 @@ 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 ch = ISALPHANUM ch alreadyEncodedFS :: FAST_STRING -> Bool @@ -547,9 +476,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 @@ -561,7 +491,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 @@ -581,6 +510,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" @@ -594,6 +524,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 @@ -613,16 +545,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 @@ -636,6 +569,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 @@ -674,32 +609,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'#