X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FbasicTypes%2FOccName.lhs;h=4ff4c87c6b177bbc03e13b4d0d5ae6939528e6cd;hb=52bd2cc7a9f328e6a7f3f50ac0055a5361f457c1;hp=139a17f5547e5ee671564ed34bb0ea13d21ec172;hpb=88ca0162dc43bf5c36a7fd8af490895a6bacecd9;p=ghc-hetmet.git diff --git a/ghc/compiler/basicTypes/OccName.lhs b/ghc/compiler/basicTypes/OccName.lhs index 139a17f..4ff4c87 100644 --- a/ghc/compiler/basicTypes/OccName.lhs +++ b/ghc/compiler/basicTypes/OccName.lhs @@ -1,4 +1,5 @@ - +{-% DrIFT (Automatic class derivations for Haskell) v1.1 %-} +% % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % @@ -6,39 +7,34 @@ \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, + tvName, srcDataName, nameSpaceString, -- The OccName type OccName, -- Abstract, instance of Outputable pprOccName, - mkSrcOccFS, mkSysOcc, mkSysOccFS, mkSrcVarOcc, mkKindOccFS, + mkOccFS, mkSysOcc, mkSysOccFS, mkFCallOcc, mkKindOccFS, + mkVarOcc, mkVarOccEncoded, mkSuperDictSelOcc, mkDFunOcc, mkForeignExportOcc, - mkDictOcc, mkWorkerOcc, mkMethodOcc, mkDefaultMethodOcc, - mkClassTyConOcc, mkClassDataConOcc, mkSpecOcc, + mkDictOcc, mkIPOcc, mkWorkerOcc, mkMethodOcc, mkDefaultMethodOcc, + mkDerivedTyConOcc, mkClassTyConOcc, mkClassDataConOcc, mkSpecOcc, + mkGenOcc1, mkGenOcc2, mkLocalOcc, mkDataTOcc, mkDataCOcc, + mkDataConWrapperOcc, mkDataConWorkerOcc, - isTvOcc, isDataOcc, isDataSymOcc, isSymOcc, + isTvOcc, isTcOcc, isDataOcc, isDataSymOcc, isSymOcc, isValOcc, + reportIfUnused, - occNameFS, occNameString, occNameUserString, occNameSpace, occNameFlavour, + occNameFS, occNameString, occNameUserString, occNameSpace, + occNameFlavour, briefOccNameFlavour, setOccNameSpace, -- Tidying up 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, @@ -49,11 +45,15 @@ 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 Unique ( Unique ) import FiniteMap ( FiniteMap, emptyFM, lookupFM, addToFM, elemFM ) +import FastString import Outputable -import GlaExts +import Binary + +import GLAEXTS \end{code} We hold both module names and identifier names in a 'Z-encoded' form @@ -68,8 +68,8 @@ 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 EncodedFS = FAST_STRING -- Encoded form +type UserFS = FastString -- As the user typed it +type EncodedFS = FastString -- Encoded form type UserString = String -- As the user typed it type EncodedString = String -- Encoded form @@ -78,125 +78,12 @@ 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 '!' + if userStyle sty + -- ftext (decodeFS fs) would needlessly pack the string again + then text (decode (unpackFS fs)) + else ftext 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} @@ -204,12 +91,31 @@ moduleIfaceFlavour (Module _ hif) = hif %************************************************************************ \begin{code} -data NameSpace = VarName -- Variables - | DataName -- Data constructors +data NameSpace = VarName -- Variables, including "source" data constructors + | DataName -- "Real" data constructors | TvName -- Type 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 ) + {-! derive: Binary !-} + +-- Note [Data Constructors] +-- see also: Note [Data Constructor Naming] in DataCon.lhs +-- +-- "Source" data constructors are the data constructors mentioned +-- in Haskell source code +-- +-- "Real" data constructors are the data constructors of the +-- representation type, which may not be the same as the source +-- type + +-- Example: +-- data T = T !(Int,Int) +-- +-- The source datacon has type (Int,Int) -> T +-- The real datacon has type Int -> Int -> T +-- GHC chooses a representation based on the strictness etc. + -- Though type constructors and classes are in the same name space now, -- the NameSpace type is abstract, so we can easily separate them later @@ -217,10 +123,12 @@ tcName = TcClsName -- Type constructors clsName = TcClsName -- Classes tcClsName = TcClsName -- Not sure which! -dataName = DataName -tvName = TvName -varName = VarName +dataName = DataName +srcDataName = DataName -- Haskell-source data constructors should be + -- in the Data name space +tvName = TvName +varName = VarName nameSpaceString :: NameSpace -> String nameSpaceString DataName = "Data constructor" @@ -240,6 +148,7 @@ nameSpaceString TcClsName = "Type constructor or class" data OccName = OccName NameSpace EncodedFS + {-! derive : Binary !-} \end{code} @@ -279,14 +188,21 @@ already encoded \begin{code} mkSysOcc :: NameSpace -> EncodedString -> OccName -mkSysOcc occ_sp str = ASSERT( alreadyEncoded str ) - OccName occ_sp (_PK_ str) +mkSysOcc occ_sp str = ASSERT2( alreadyEncoded str, text str ) + OccName occ_sp (mkFastString str) mkSysOccFS :: NameSpace -> EncodedFS -> OccName mkSysOccFS occ_sp fs = ASSERT2( alreadyEncodedFS fs, ppr fs ) OccName occ_sp fs --- Kind constructors get a speical function. Uniquely, they are not encoded, +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! +mkFCallOcc str = OccName varName (mkFastString str) + +-- 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. @@ -297,11 +213,14 @@ 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) + +mkVarOcc :: UserFS -> OccName +mkVarOcc fs = mkSysOccFS varName (encodeFS fs) -mkSrcVarOcc :: UserFS -> OccName -mkSrcVarOcc fs = mkSysOccFS varName (encodeFS fs) +mkVarOccEncoded :: EncodedFS -> OccName +mkVarOccEncoded fs = mkSysOccFS varName fs \end{code} @@ -317,7 +236,7 @@ occNameFS :: OccName -> EncodedFS occNameFS (OccName _ s) = s occNameString :: OccName -> EncodedString -occNameString (OccName _ s) = _UNPK_ s +occNameString (OccName _ s) = unpackFS s occNameUserString :: OccName -> UserString occNameUserString occ = decode (occNameString occ) @@ -325,27 +244,46 @@ occNameUserString occ = decode (occNameString occ) occNameSpace :: OccName -> NameSpace occNameSpace (OccName sp _) = sp -setOccNameSpace :: OccName -> NameSpace -> OccName -setOccNameSpace (OccName _ occ) sp = OccName sp occ +setOccNameSpace :: NameSpace -> OccName -> OccName +setOccNameSpace sp (OccName _ occ) = OccName sp occ -- occNameFlavour is used only to generate good error messages occNameFlavour :: OccName -> String -occNameFlavour (OccName sp _) = nameSpaceString sp +occNameFlavour (OccName DataName _) = "Data constructor" +occNameFlavour (OccName TvName _) = "Type variable" +occNameFlavour (OccName TcClsName _) = "Type constructor or class" +occNameFlavour (OccName VarName s) = "Variable" + +-- briefOccNameFlavour is used in debug-printing of names +briefOccNameFlavour :: OccName -> String +briefOccNameFlavour (OccName DataName _) = "d" +briefOccNameFlavour (OccName VarName _) = "v" +briefOccNameFlavour (OccName TvName _) = "tv" +briefOccNameFlavour (OccName TcClsName _) = "tc" \end{code} \begin{code} -isTvOcc, isDataSymOcc, isSymOcc :: OccName -> Bool +isTvOcc, isDataSymOcc, isSymOcc, isTcOcc :: OccName -> Bool isTvOcc (OccName TvName _) = True isTvOcc other = False +isTcOcc (OccName TcClsName _) = True +isTcOcc 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 (OccName VarName s) = isLexConSym (decodeFS s) isDataSymOcc other = False isDataOcc (OccName DataName _) = True -isDataOcc oter = False +isDataOcc (OccName VarName s) = isLexCon (decodeFS s) +isDataOcc other = False -- Any operator (data constructor or variable) -- Pretty inefficient! @@ -354,6 +292,17 @@ isSymOcc (OccName VarName s) = isLexSym (decodeFS s) \end{code} +\begin{code} +reportIfUnused :: OccName -> Bool + -- Haskell 98 encourages compilers to suppress warnings about + -- unused names in a pattern if they start with "_". +reportIfUnused occ = case occNameUserString occ of + ('_' : _) -> False + zz_other -> True +\end{code} + + + %************************************************************************ %* * \subsection{Making system names} @@ -366,74 +315,93 @@ 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 - $D... ...ditto data cons + :T... compiler-generated tycons for dictionaries + :D... ...ditto data cons $sf.. specialised version of f in encoded form these appear as Zdfxxx etc :... keywords (export:, letrec: etc.) +--- I THINK THIS IS WRONG! This knowledge is encoded in the following functions. -@mk_deriv@ generates an @OccName@ from the one-char prefix and a string. +@mk_deriv@ generates an @OccName@ from the prefix and a string. NB: The string must already be encoded! \begin{code} mk_deriv :: NameSpace -> String -- Distinguishes one sort of derived name from another -> EncodedString -- Must be already encoded!! We don't want to encode it a - -- second time because encoding isn't itempotent + -- second time because encoding isn't idempotent -> OccName mk_deriv occ_sp sys_prefix str = mkSysOcc occ_sp (encode sys_prefix ++ str) \end{code} \begin{code} -mkDictOcc, mkWorkerOcc, 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" -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 -mkDictOcc = mk_simple_deriv varName "$d" -mkSpecOcc = mk_simple_deriv varName "$s" -mkForeignExportOcc = mk_simple_deriv varName "$f" +mkDataConWrapperOcc = mk_simple_deriv varName "$W" +mkWorkerOcc = mk_simple_deriv varName "$w" +mkDefaultMethodOcc = mk_simple_deriv varName "$dm" +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" -- We go straight to the "real" data con + -- for datacons from classes +mkDictOcc = mk_simple_deriv varName "$d" +mkIPOcc = mk_simple_deriv varName "$i" +mkSpecOcc = mk_simple_deriv varName "$s" +mkForeignExportOcc = mk_simple_deriv varName "$f" + +-- Generic derivable classes +mkGenOcc1 = mk_simple_deriv varName "$gfrom" +mkGenOcc2 = mk_simple_deriv varName "$gto" + +-- data T = MkT ... deriving( Data ) needs defintions for +-- $tT :: Data.Generics.Basics.DataType +-- $cMkT :: Data.Generics.Basics.Constr +mkDataTOcc = mk_simple_deriv varName "$t" +mkDataCOcc = mk_simple_deriv varName "$c" mk_simple_deriv sp px occ = mk_deriv sp px (occNameString occ) + + +-- Data constructor workers are made by setting the name space +-- of the data constructor OccName (which should be a DataName) +-- to DataName +mkDataConWorkerOcc datacon_occ = setOccNameSpace varName datacon_occ \end{code} \begin{code} mkSuperDictSelOcc :: Int -- Index of superclass, eg 3 -> OccName -- Class, eg "Ord" - -> OccName -- eg "p3Ord" + -> OccName -- eg "$p3Ord" mkSuperDictSelOcc index cls_occ = mk_deriv varName "$p" (show index ++ occNameString cls_occ) + +mkLocalOcc :: Unique -- Unique + -> OccName -- Local name (e.g. "sat") + -> OccName -- Nice unique version ("$L23sat") +mkLocalOcc uniq occ + = mk_deriv varName ("$L" ++ show uniq) (occNameString occ) + -- The Unique might print with characters + -- that need encoding (e.g. 'z'!) \end{code} \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) - where - cls_str = occNameString cls_occ - tycon_str = occNameString tycon_occ - show_index | index == 0 = "" - | otherwise = show index +mkDFunOcc :: EncodedString -- Typically the class and type glommed together e.g. "OrdMaybe" + -> OccName -- "$fOrdMaybe" + +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 @@ -480,7 +448,7 @@ because that isn't a single lexeme. So we encode it to 'lle' and *then* tack on the '1', if necessary. \begin{code} -type TidyOccEnv = FiniteMap FAST_STRING Int -- The in-scope OccNames +type TidyOccEnv = FiniteMap FastString Int -- The in-scope OccNames emptyTidyOccEnv = emptyFM initTidyOccEnv :: [OccName] -> TidyOccEnv -- Initialise with names to avoid! @@ -493,7 +461,7 @@ tidyOccName in_scope occ@(OccName occ_sp fs) = (addToFM in_scope fs 1, occ) -- First occurrence | otherwise -- Already occurs - = go in_scope (_UNPK_ fs) + = go in_scope (unpackFS fs) where go in_scope str = case lookupFM in_scope pk_str of @@ -504,7 +472,7 @@ tidyOccName in_scope occ@(OccName occ_sp fs) Nothing -> (addToFM in_scope pk_str 1, mkSysOccFS occ_sp pk_str) -- str is now unique where - pk_str = _PK_ str + pk_str = mkFastString str \end{code} @@ -522,32 +490,34 @@ 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 - () Z0T - (,,,,) Z4T - + :+ ZCzp + () Z0T 0-tuple + (,,,,) Z5T 5-tuple + (# #) Z1H unboxed 1-tuple (note the space) + (#,,,,#) Z5H unboxed 5-tuple + (NB: There is no Z1T nor Z0H.) \begin{code} -- alreadyEncoded is used in ASSERTs to check for encoded @@ -556,40 +526,50 @@ The basic encoding scheme is this. alreadyEncoded :: String -> Bool alreadyEncoded s = all ok s where - ok '_' = True - ok ch = ISALPHANUM ch + 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 -alreadyEncodedFS fs = alreadyEncoded (_UNPK_ fs) +alreadyEncodedFS :: FastString -> Bool +alreadyEncodedFS fs = alreadyEncoded (unpackFS 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 cs -maybe_tuple other = Nothing +maybe_tuple "(# #)" = Just("Z1H") +maybe_tuple ('(' : '#' : cs) = case count_commas (0::Int) cs of + (n, '#' : ')' : cs) -> Just ('Z' : shows (n+1) "H") + other -> Nothing +maybe_tuple "()" = Just("Z0T") +maybe_tuple ('(' : cs) = case count_commas (0::Int) cs of + (n, ')' : cs) -> Just ('Z' : shows (n+1) "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 - | otherwise = _PK_ (encode str) + | otherwise = mkFastString (encode str) where - str = _UNPK_ fast_str + str = unpackFS 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 +unencodedChar c = c >= 'a' && c <= 'z' + || c >= 'A' && c <= 'Z' + || c >= '0' && c <= '9' encode_ch :: Char -> EncodedString encode_ch c | unencodedChar c = [c] -- Common case first @@ -606,6 +586,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" @@ -619,16 +600,16 @@ encode_ch '\'' = "zq" encode_ch '\\' = "zr" encode_ch '/' = "zs" encode_ch '*' = "zt" -encode_ch c = ['z', 'x', intToDigit hi, intToDigit lo] - where - (hi,lo) = ord c `quotRem` 16 +encode_ch '_' = "zu" +encode_ch '%' = "zv" +encode_ch c = 'z' : shows (ord c) "U" \end{code} Decode is used for user printing. \begin{code} -decodeFS :: FAST_STRING -> FAST_STRING -decodeFS fs = _PK_ (decode (_UNPK_ fs)) +decodeFS :: FastString -> FastString +decodeFS fs = mkFastString (decode (unpackFS fs)) decode :: EncodedString -> UserString decode [] = [] @@ -638,16 +619,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 @@ -661,23 +643,30 @@ 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 ('x' : d1 : d2 : rest) = chr (digitToInt d1 * 16 + digitToInt d2) : decode rest +decode_escape ('u' : rest) = '_' : decode rest +decode_escape ('v' : rest) = '%' : 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 0 ('T' : rest) = "()" ++ (decode rest) + go n ('T' : rest) = '(' : replicate (n-1) ',' ++ ')' : decode rest + go 1 ('H' : rest) = "(# #)" ++ (decode rest) + go n ('H' : rest) = '(' : '#' : replicate (n-1) ',' ++ '#' : ')' : 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) +decode_escape [] = pprTrace "decode_escape" (text "empty") "" \end{code} %************************************************************************ %* * -n\subsection{Lexical categories} +\subsection{Lexical categories} %* * %************************************************************************ @@ -685,8 +674,8 @@ These functions test strings to see if they fit the lexical categories defined in the Haskell report. \begin{code} -isLexCon, isLexVar, isLexId, isLexSym :: FAST_STRING -> Bool -isLexConId, isLexConSym, isLexVarId, isLexVarSym :: FAST_STRING -> Bool +isLexCon, isLexVar, isLexId, isLexSym :: FastString -> Bool +isLexConId, isLexConSym, isLexVarId, isLexVarSym :: FastString -> Bool isLexCon cs = isLexConId cs || isLexConSym cs isLexVar cs = isLexVarId cs || isLexVarSym cs @@ -697,34 +686,31 @@ 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 + | nullFastString cs = False -- e.g. "Foo", "[]", "(,)" + | cs == FSLIT("[]") = True + | otherwise = startsConId (headFS cs) isLexVarId cs -- Ordinary prefix identifiers - | _NULL_ cs = False -- e.g. "x", "_x" - | otherwise = isLower c || isLowerISO c || c == '_' - where - c = _HEAD_ cs + | nullFastString cs = False -- e.g. "x", "_x" + | otherwise = startsVarId (headFS cs) isLexConSym cs -- Infix type or data constructors - | _NULL_ cs = False -- e.g. ":-:", ":", "->" - | otherwise = c == ':' - || cs == SLIT("->") - where - c = _HEAD_ cs + | nullFastString cs = False -- e.g. ":-:", ":", "->" + | cs == FSLIT("->") = True + | otherwise = startsConSym (headFS cs) isLexVarSym cs -- Infix identifiers - | _NULL_ cs = False -- e.g. "+" - | otherwise = isSymbolASCII c - || isSymbolISO c - where - c = _HEAD_ cs + | nullFastString cs = False -- e.g. "+" + | otherwise = startsVarSym (headFS 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'# @@ -732,3 +718,34 @@ isUpperISO (C# c#) = c# `geChar#` '\xc0'# && c# `leChar#` '\xde'# && c# `neCh isLowerISO (C# c#) = c# `geChar#` '\xdf'# && c# `leChar#` '\xff'# && c# `neChar#` '\xf7'# --0xdf <= oc && oc <= 0xff && oc /= 0xf7 where oc = ord c \end{code} +\begin{code} +{-* Generated by DrIFT-v1.0 : Look, but Don't Touch. *-} +instance Binary NameSpace where + put_ bh VarName = do + putByte bh 0 + put_ bh DataName = do + putByte bh 1 + put_ bh TvName = do + putByte bh 2 + put_ bh TcClsName = do + putByte bh 3 + get bh = do + h <- getByte bh + case h of + 0 -> do return VarName + 1 -> do return DataName + 2 -> do return TvName + _ -> do return TcClsName + +instance Binary OccName where + put_ bh (OccName aa ab) = do + put_ bh aa + put_ bh ab + get bh = do + aa <- get bh + ab <- get bh + return (OccName aa ab) + +-- Imported from other files :- + +\end{code}