X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FbasicTypes%2FOccName.lhs;h=e10d43fc27c178020fbaa6adaa6871f09f5c16a0;hb=b085ee40c7f265a5977ea6ec1c415e573be5ff8c;hp=d14267bd8008451e17962b08f3b6584f993a98a3;hpb=db7041f72b7c7d0114e47b7305058fae48fb0ade;p=ghc-hetmet.git diff --git a/ghc/compiler/basicTypes/OccName.lhs b/ghc/compiler/basicTypes/OccName.lhs index d14267b..e10d43f 100644 --- a/ghc/compiler/basicTypes/OccName.lhs +++ b/ghc/compiler/basicTypes/OccName.lhs @@ -1,3 +1,4 @@ +{-% DrIFT (Automatic class derivations for Haskell) v1.1 %-} % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % @@ -14,13 +15,14 @@ module OccName ( OccName, -- Abstract, instance of Outputable pprOccName, - mkOccFS, mkSysOcc, mkSysOccFS, mkCCallOcc, mkVarOcc, mkKindOccFS, + mkOccFS, mkSysOcc, mkSysOccFS, mkFCallOcc, mkKindOccFS, + mkVarOcc, mkVarOccEncoded, mkSuperDictSelOcc, mkDFunOcc, mkForeignExportOcc, mkDictOcc, mkIPOcc, mkWorkerOcc, mkMethodOcc, mkDefaultMethodOcc, mkDerivedTyConOcc, mkClassTyConOcc, mkClassDataConOcc, mkSpecOcc, - mkGenOcc1, mkGenOcc2, + mkGenOcc1, mkGenOcc2, mkLocalOcc, - isSysOcc, isTvOcc, isDataOcc, isDataSymOcc, isSymOcc, isValOcc, + isTvOcc, isTcOcc, isDataOcc, isDataSymOcc, isSymOcc, isValOcc, occNameFS, occNameString, occNameUserString, occNameSpace, occNameFlavour, setOccNameSpace, @@ -40,10 +42,14 @@ module OccName ( #include "HsVersions.h" -import Char ( isDigit, isUpper, isLower, ISALPHANUM, ord, chr, digitToInt ) +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 Binary + import GlaExts \end{code} @@ -59,8 +65,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 @@ -70,9 +76,9 @@ pprEncodedFS :: EncodedFS -> SDoc pprEncodedFS fs = getPprStyle $ \ sty -> if userStyle sty - -- ptext (decodeFS fs) would needlessly pack the string again - then text (decode (_UNPK_ fs)) - else ptext fs + -- ftext (decodeFS fs) would needlessly pack the string again + then text (decode (unpackFS fs)) + else ftext fs \end{code} %************************************************************************ @@ -88,6 +94,7 @@ data NameSpace = VarName -- Variables | TcClsName -- Type constructors and classes; Haskell has them -- in the same name space for now. deriving( Eq, Ord ) + {-! derive: Binary !-} -- Though type constructors and classes are in the same name space now, -- the NameSpace type is abstract, so we can easily separate them later @@ -118,6 +125,7 @@ nameSpaceString TcClsName = "Type constructor or class" data OccName = OccName NameSpace EncodedFS + {-! derive : Binary !-} \end{code} @@ -158,18 +166,18 @@ already encoded \begin{code} mkSysOcc :: NameSpace -> EncodedString -> OccName mkSysOcc occ_sp str = ASSERT2( alreadyEncoded str, text str ) - OccName occ_sp (_PK_ str) + OccName occ_sp (mkFastString str) 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 (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* @@ -187,6 +195,9 @@ mkOccFS occ_sp fs = mkSysOccFS occ_sp (encodeFS fs) mkVarOcc :: UserFS -> OccName mkVarOcc fs = mkSysOccFS varName (encodeFS fs) + +mkVarOccEncoded :: EncodedFS -> OccName +mkVarOccEncoded fs = mkSysOccFS varName fs \end{code} @@ -202,7 +213,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) @@ -219,11 +230,14 @@ occNameFlavour (OccName sp _) = nameSpaceString sp \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 @@ -258,25 +272,26 @@ Here's our convention for splitting up the interface file name space: $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) @@ -288,33 +303,34 @@ mkDictOcc, mkIPOcc, mkWorkerOcc, mkDefaultMethodOcc, :: 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" -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" +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" -- +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) - - -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} 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} @@ -369,7 +385,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! @@ -382,7 +398,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 @@ -393,7 +409,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} @@ -433,13 +449,12 @@ The basic encoding scheme is this. foo## foozhzh foo##1 foozhzh1 fooZ fooZZ - :+ Zczp - () Z0T - (,,,,) 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.) + :+ 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 @@ -453,10 +468,10 @@ alreadyEncoded s = all ok s -- 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 + 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 @@ -466,11 +481,13 @@ encode cs = case maybe_tuple cs of go [] = [] go (c:cs) = encode_ch c ++ go cs +maybe_tuple "(# #)" = Just("Z1H") maybe_tuple ('(' : '#' : cs) = case count_commas (0::Int) cs of - (n, '#' : ')' : cs) -> Just ('Z' : shows n "H") + (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 "T") + (n, ')' : cs) -> Just ('Z' : shows (n+1) "T") other -> Nothing maybe_tuple other = Nothing @@ -480,14 +497,16 @@ 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 '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 @@ -526,8 +545,8 @@ encode_ch c = 'z' : shows (ord c) "U" 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 [] = [] @@ -570,18 +589,21 @@ 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 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} %* * %************************************************************************ @@ -589,8 +611,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 @@ -601,22 +623,22 @@ isLexSym cs = isLexConSym cs || isLexVarSym cs ------------- isLexConId cs -- Prefix type or data constructors - | _NULL_ cs = False -- e.g. "Foo", "[]", "(,)" - | cs == SLIT("[]") = True - | otherwise = startsConId (_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 = startsVarId (_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. ":-:", ":", "->" - | cs == SLIT("->") = True - | otherwise = startsConSym (_HEAD_ cs) + | nullFastString cs = False -- e.g. ":-:", ":", "->" + | cs == FSLIT("->") = True + | otherwise = startsConSym (headFS cs) isLexVarSym cs -- Infix identifiers - | _NULL_ cs = False -- e.g. "+" - | otherwise = startsVarSym (_HEAD_ cs) + | nullFastString cs = False -- e.g. "+" + | otherwise = startsVarSym (headFS cs) ------------- startsVarSym, startsVarId, startsConSym, startsConId :: Char -> Bool @@ -633,3 +655,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}