[project @ 2000-01-28 20:52:37 by lewie]
[ghc-hetmet.git] / ghc / compiler / basicTypes / OccName.lhs
1
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4
5 \section[OccName]{@OccName@}
6
7 \begin{code}
8 module OccName (
9         -- The NameSpace type; abstact
10         NameSpace, tcName, clsName, tcClsName, dataName, varName, ipName,
11         tvName, uvName, nameSpaceString, 
12
13         -- The OccName type
14         OccName,        -- Abstract, instance of Outputable
15         pprOccName, 
16
17         mkSrcOccFS, mkSysOcc, mkSysOccFS, mkSrcVarOcc, mkKindOccFS,
18         mkSuperDictSelOcc, mkDFunOcc, mkForeignExportOcc,
19         mkDictOcc, mkIPOcc, mkWorkerOcc, mkMethodOcc, mkDefaultMethodOcc,
20         mkDerivedTyConOcc, mkClassTyConOcc, mkClassDataConOcc, mkSpecOcc,
21         
22         isTvOcc, isUvOcc, isDataOcc, isDataSymOcc, isSymOcc, isIPOcc,
23
24         occNameFS, occNameString, occNameUserString, occNameSpace, occNameFlavour, 
25         setOccNameSpace,
26
27         -- Tidying up
28         TidyOccEnv, emptyTidyOccEnv, tidyOccName, initTidyOccEnv,
29
30         -- Encoding
31         EncodedString, EncodedFS, UserString, UserFS, encode, encodeFS, decode, pprEncodedFS,
32
33         -- The basic form of names
34         isLexCon, isLexVar, isLexId, isLexSym,
35         isLexConId, isLexConSym, isLexVarId, isLexVarSym,
36         isLowerISO, isUpperISO
37
38     ) where
39
40 #include "HsVersions.h"
41
42 import Char     ( isDigit, isAlpha, isUpper, isLower, ISALPHANUM, ord, chr, digitToInt, intToDigit )
43 import Util     ( thenCmp )
44 import FiniteMap ( FiniteMap, emptyFM, lookupFM, addToFM, elemFM )
45 import Outputable
46 import GlaExts
47 \end{code}
48
49 We hold both module names and identifier names in a 'Z-encoded' form
50 that makes them acceptable both as a C identifier and as a Haskell
51 (prefix) identifier. 
52
53 They can always be decoded again when printing error messages
54 or anything else for the user, but it does make sense for it
55 to be represented here in encoded form, so that when generating
56 code the encoding operation is not performed on each occurrence.
57
58 These type synonyms help documentation.
59
60 \begin{code}
61 type UserFS    = FAST_STRING    -- As the user typed it
62 type EncodedFS = FAST_STRING    -- Encoded form
63
64 type UserString = String        -- As the user typed it
65 type EncodedString = String     -- Encoded form
66
67
68 pprEncodedFS :: EncodedFS -> SDoc
69 pprEncodedFS fs
70   = getPprStyle         $ \ sty ->
71     if userStyle sty then
72         text (decode (_UNPK_ fs))
73     else
74         ptext fs
75 \end{code}
76
77 %************************************************************************
78 %*                                                                      *
79 \subsection{Name space}
80 %*                                                                      *
81 %************************************************************************
82
83 \begin{code}
84 data NameSpace = VarName        -- Variables
85                | IPName         -- Implicit Parameters
86                | DataName       -- Data constructors
87                | TvName         -- Type variables
88                | UvName         -- Usage variables
89                | TcClsName      -- Type constructors and classes; Haskell has them
90                                 -- in the same name space for now.
91                deriving( Eq, Ord )
92
93 -- Though type constructors and classes are in the same name space now,
94 -- the NameSpace type is abstract, so we can easily separate them later
95 tcName    = TcClsName           -- Type constructors
96 clsName   = TcClsName           -- Classes
97 tcClsName = TcClsName           -- Not sure which!
98
99 dataName = DataName
100 tvName   = TvName
101 uvName   = UvName
102 varName  = VarName
103 ipName   = IPName
104
105
106 nameSpaceString :: NameSpace -> String
107 nameSpaceString DataName  = "Data constructor"
108 nameSpaceString VarName   = "Variable"
109 nameSpaceString IPName    = "Implicit Param"
110 nameSpaceString TvName    = "Type variable"
111 nameSpaceString UvName    = "Usage variable"
112 nameSpaceString TcClsName = "Type constructor or class"
113 \end{code}
114
115
116 %************************************************************************
117 %*                                                                      *
118 \subsection[Name-pieces-datatypes]{The @OccName@ datatypes}
119 %*                                                                      *
120 %************************************************************************
121
122 \begin{code}
123 data OccName = OccName 
124                         NameSpace
125                         EncodedFS
126 \end{code}
127
128
129 \begin{code}
130 instance Eq OccName where
131     (OccName sp1 s1) == (OccName sp2 s2) = s1 == s2 && sp1 == sp2
132
133 instance Ord OccName where
134     compare (OccName sp1 s1) (OccName sp2 s2) = (s1  `compare` s2) `thenCmp`
135                                                 (sp1 `compare` sp2)
136 \end{code}
137
138
139 %************************************************************************
140 %*                                                                      *
141 \subsection{Printing}
142 %*                                                                      *
143 %************************************************************************
144  
145 \begin{code}
146 instance Outputable OccName where
147     ppr = pprOccName
148
149 pprOccName :: OccName -> SDoc
150 pprOccName (OccName sp occ) = pprEncodedFS occ
151 \end{code}
152
153
154 %************************************************************************
155 %*                                                                      *
156 \subsection{Construction}
157 %*                                                                      *
158 %************************************************************************
159
160 *Sys* things do no encoding; the caller should ensure that the thing is
161 already encoded
162
163 \begin{code}
164 mkSysOcc :: NameSpace -> EncodedString -> OccName
165 mkSysOcc occ_sp str = ASSERT( alreadyEncoded str )
166                       OccName occ_sp (_PK_ str)
167
168 mkSysOccFS :: NameSpace -> EncodedFS -> OccName
169 mkSysOccFS occ_sp fs = ASSERT2( alreadyEncodedFS fs, ppr fs )
170                        OccName occ_sp fs
171
172 -- Kind constructors get a speical function.  Uniquely, they are not encoded,
173 -- so that they have names like '*'.  This means that *even in interface files*
174 -- we'll get kinds like (* -> (* -> *)).  We can't use mkSysOcc because it
175 -- has an ASSERT that doesn't hold.
176 mkKindOccFS :: NameSpace -> EncodedFS -> OccName
177 mkKindOccFS occ_sp fs = OccName occ_sp fs
178 \end{code}
179
180 *Source-code* things are encoded.
181
182 \begin{code}
183 mkSrcOccFS :: NameSpace -> UserFS -> OccName
184 mkSrcOccFS occ_sp fs = mkSysOccFS occ_sp (encodeFS fs)
185
186 mkSrcVarOcc :: UserFS -> OccName
187 mkSrcVarOcc fs = mkSysOccFS varName (encodeFS fs)
188 \end{code}
189
190
191
192 %************************************************************************
193 %*                                                                      *
194 \subsection{Predicates and taking them apart}
195 %*                                                                      *
196 %************************************************************************
197
198 \begin{code} 
199 occNameFS :: OccName -> EncodedFS
200 occNameFS (OccName _ s) = s
201
202 occNameString :: OccName -> EncodedString
203 occNameString (OccName _ s) = _UNPK_ s
204
205 occNameUserString :: OccName -> UserString
206 occNameUserString occ = decode (occNameString occ)
207
208 occNameSpace :: OccName -> NameSpace
209 occNameSpace (OccName sp _) = sp
210
211 setOccNameSpace :: OccName -> NameSpace -> OccName
212 setOccNameSpace (OccName _ occ) sp = OccName sp occ
213
214 -- occNameFlavour is used only to generate good error messages
215 occNameFlavour :: OccName -> String
216 occNameFlavour (OccName sp _) = nameSpaceString sp
217 \end{code}
218
219 \begin{code}
220 isTvOcc, isDataSymOcc, isSymOcc, isUvOcc :: OccName -> Bool
221
222 isTvOcc (OccName TvName _) = True
223 isTvOcc other              = False
224
225 isUvOcc (OccName UvName _) = True
226 isUvOcc other              = False
227
228 -- Data constructor operator (starts with ':', or '[]')
229 -- Pretty inefficient!
230 isDataSymOcc (OccName DataName s) = isLexConSym (decodeFS s)
231 isDataSymOcc other                = False
232
233 isDataOcc (OccName DataName _) = True
234 isDataOcc oter                 = False
235
236 -- Any operator (data constructor or variable)
237 -- Pretty inefficient!
238 isSymOcc (OccName DataName s) = isLexConSym (decodeFS s)
239 isSymOcc (OccName VarName s)  = isLexSym (decodeFS s)
240
241 isIPOcc (OccName IPName _) = True
242 isIPOcc _                  = False
243 \end{code}
244
245
246 %************************************************************************
247 %*                                                                      *
248 \subsection{Making system names}
249 %*                                                                      *
250 %************************************************************************
251
252 Here's our convention for splitting up the interface file name space:
253
254         d...            dictionary identifiers
255                         (local variables, so no name-clash worries)
256
257         $f...           dict-fun identifiers (from inst decls)
258         $dm...          default methods
259         $p...           superclass selectors
260         $w...           workers
261         $T...           compiler-generated tycons for dictionaries
262         $D...           ...ditto data cons
263         $sf..           specialised version of f
264
265         in encoded form these appear as Zdfxxx etc
266
267         :...            keywords (export:, letrec: etc.)
268
269 This knowledge is encoded in the following functions.
270
271
272 @mk_deriv@ generates an @OccName@ from the one-char prefix and a string.
273 NB: The string must already be encoded!
274
275 \begin{code}
276 mk_deriv :: NameSpace 
277          -> String              -- Distinguishes one sort of derived name from another
278          -> EncodedString       -- Must be already encoded!!  We don't want to encode it a 
279                                 -- second time because encoding isn't itempotent
280          -> OccName
281
282 mk_deriv occ_sp sys_prefix str = mkSysOcc occ_sp (encode sys_prefix ++ str)
283 \end{code}
284
285 \begin{code}
286 mkDictOcc, mkIPOcc, mkWorkerOcc, mkDefaultMethodOcc,
287            mkClassTyConOcc, mkClassDataConOcc, mkSpecOcc
288    :: OccName -> OccName
289
290 -- These derived variables have a prefix that no Haskell value could have
291 mkWorkerOcc        = mk_simple_deriv varName  "$w"
292 mkDefaultMethodOcc = mk_simple_deriv varName  "$dm"
293 mkDerivedTyConOcc  = mk_simple_deriv tcName   ":"       -- The : prefix makes sure it classifies
294 mkClassTyConOcc    = mk_simple_deriv tcName   ":T"      -- as a tycon/datacon
295 mkClassDataConOcc  = mk_simple_deriv dataName ":D"      --
296 mkDictOcc          = mk_simple_deriv varName  "$d"
297 mkIPOcc            = mk_simple_deriv varName  "$i"
298 mkSpecOcc          = mk_simple_deriv varName  "$s"
299 mkForeignExportOcc = mk_simple_deriv varName  "$f"
300
301 mk_simple_deriv sp px occ = mk_deriv sp px (occNameString occ)
302 \end{code}
303
304 \begin{code}
305 mkSuperDictSelOcc :: Int        -- Index of superclass, eg 3
306                   -> OccName    -- Class, eg "Ord"
307                   -> OccName    -- eg "p3Ord"
308 mkSuperDictSelOcc index cls_occ
309   = mk_deriv varName "$p" (show index ++ occNameString cls_occ)
310 \end{code}
311
312
313 \begin{code}
314 mkDFunOcc :: EncodedString      -- Typically the class and type glommed together e.g. "OrdMaybe"
315           -> Int                -- Unique to distinguish dfuns which share the previous two
316                                 --      eg 3
317           -- The requirement is that the (string,index) pair be unique in this module
318
319           -> OccName    -- "$fOrdMaybe3"
320
321 mkDFunOcc string index
322   = mk_deriv VarName "$f" (show_index ++ string)
323   where
324     show_index | index == 0 = ""
325                | otherwise  = show index
326 \end{code}
327
328 We used to add a '$m' to indicate a method, but that gives rise to bad
329 error messages from the type checker when we print the function name or pattern
330 of an instance-decl binding.  Why? Because the binding is zapped
331 to use the method name in place of the selector name.
332 (See TcClassDcl.tcMethodBind)
333
334 The way it is now, -ddump-xx output may look confusing, but
335 you can always say -dppr-debug to get the uniques.
336
337 However, we *do* have to zap the first character to be lower case,
338 because overloaded constructors (blarg) generate methods too.
339 And convert to VarName space
340
341 e.g. a call to constructor MkFoo where
342         data (Ord a) => Foo a = MkFoo a
343
344 If this is necessary, we do it by prefixing '$m'.  These 
345 guys never show up in error messages.  What a hack.
346
347 \begin{code}
348 mkMethodOcc :: OccName -> OccName
349 mkMethodOcc occ@(OccName VarName fs) = occ
350 mkMethodOcc occ                      = mk_simple_deriv varName "$m" occ
351 \end{code}
352
353
354 %************************************************************************
355 %*                                                                      *
356 \subsection{Tidying them up}
357 %*                                                                      *
358 %************************************************************************
359
360 Before we print chunks of code we like to rename it so that
361 we don't have to print lots of silly uniques in it.  But we mustn't
362 accidentally introduce name clashes!  So the idea is that we leave the
363 OccName alone unless it accidentally clashes with one that is already
364 in scope; if so, we tack on '1' at the end and try again, then '2', and
365 so on till we find a unique one.
366
367 There's a wrinkle for operators.  Consider '>>='.  We can't use '>>=1' 
368 because that isn't a single lexeme.  So we encode it to 'lle' and *then*
369 tack on the '1', if necessary.
370
371 \begin{code}
372 type TidyOccEnv = FiniteMap FAST_STRING Int     -- The in-scope OccNames
373 emptyTidyOccEnv = emptyFM
374
375 initTidyOccEnv :: [OccName] -> TidyOccEnv       -- Initialise with names to avoid!
376 initTidyOccEnv = foldl (\env (OccName _ fs) -> addToFM env fs 1) emptyTidyOccEnv
377
378 tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName)
379
380 tidyOccName in_scope occ@(OccName occ_sp fs)
381   | not (fs `elemFM` in_scope)
382   = (addToFM in_scope fs 1, occ)        -- First occurrence
383
384   | otherwise                           -- Already occurs
385   = go in_scope (_UNPK_ fs)
386   where
387
388     go in_scope str = case lookupFM in_scope pk_str of
389                         Just n  -> go (addToFM in_scope pk_str (n+1)) (str ++ show n)
390                                 -- Need to go round again, just in case "t3" (say) 
391                                 -- clashes with a "t3" that's already in scope
392
393                         Nothing -> (addToFM in_scope pk_str 1, mkSysOccFS occ_sp pk_str)
394                                 -- str is now unique
395                     where
396                       pk_str = _PK_ str
397 \end{code}
398
399
400 %************************************************************************
401 %*                                                                      *
402 \subsection{The 'Z' encoding}
403 %*                                                                      *
404 %************************************************************************
405
406 This is the main name-encoding and decoding function.  It encodes any
407 string into a string that is acceptable as a C name.  This is the name
408 by which things are known right through the compiler.
409
410 The basic encoding scheme is this.  
411
412 * Tuples (,,,) are coded as Z3T
413
414 * Alphabetic characters (upper and lower), digits, and '_'
415         all translate to themselves; 
416         except 'Z', which translates to 'ZZ'
417         and    'z', which translates to 'zz'
418   We need both so that we can preserve the variable/tycon distinction
419
420 * Most other printable characters translate to 'Zx' for some
421         alphabetic character x
422
423 * The others translate as 'Zxdd' where 'dd' is exactly two hexadecimal
424         digits for the ord of the character
425
426         Before          After
427         --------------------------
428         Trak            Trak
429         foo_wib         foo_wib
430         >               Zg
431         >1              Zg1
432         foo#            fooZh
433         foo##           fooZhZh
434         foo##1          fooZhXh1
435         fooZ            fooZZ   
436         :+              ZcZp
437         ()              Z0T
438         (,,,,)          Z4T
439
440
441 \begin{code}
442 -- alreadyEncoded is used in ASSERTs to check for encoded
443 -- strings.  It isn't fail-safe, of course, because, say 'zh' might
444 -- be encoded or not.
445 alreadyEncoded :: String -> Bool
446 alreadyEncoded s = all ok s
447                  where
448                    ok '_' = True
449                    ok ch  = ISALPHANUM ch
450
451 alreadyEncodedFS :: FAST_STRING -> Bool
452 alreadyEncodedFS fs = alreadyEncoded (_UNPK_ fs)
453
454 encode :: UserString -> EncodedString
455 encode cs = case maybe_tuple cs of
456                 Just n  -> 'Z' : show n ++ "T"          -- Tuples go to Z2T etc
457                 Nothing -> go cs
458           where
459                 go []     = []
460                 go (c:cs) = encode_ch c ++ go cs
461
462 -- ToDo: Unboxed tuples too, perhaps?
463 maybe_tuple ('(' : cs) = check_tuple (0::Int) cs
464 maybe_tuple other      = Nothing
465
466 check_tuple :: Int -> String -> Maybe Int
467 check_tuple n (',' : cs) = check_tuple (n+1) cs
468 check_tuple n ")"        = Just n
469 check_tuple n other      = Nothing
470
471 encodeFS :: UserFS -> EncodedFS
472 encodeFS fast_str  | all unencodedChar str = fast_str
473                    | otherwise             = _PK_ (encode str)
474                    where
475                      str = _UNPK_ fast_str
476
477 unencodedChar :: Char -> Bool   -- True for chars that don't need encoding
478 unencodedChar '_' = True
479 unencodedChar 'Z' = False
480 unencodedChar 'z' = False
481 unencodedChar c   = ISALPHANUM c
482
483 encode_ch :: Char -> EncodedString
484 encode_ch c | unencodedChar c = [c]     -- Common case first
485
486 -- Constructors
487 encode_ch '('  = "ZL"   -- Needed for things like (,), and (->)
488 encode_ch ')'  = "ZR"   -- For symmetry with (
489 encode_ch '['  = "ZM"
490 encode_ch ']'  = "ZN"
491 encode_ch ':'  = "ZC"
492 encode_ch 'Z'  = "ZZ"
493
494 -- Variables
495 encode_ch 'z'  = "zz"
496 encode_ch '&'  = "za"
497 encode_ch '|'  = "zb"
498 encode_ch '$'  = "zd"
499 encode_ch '='  = "ze"
500 encode_ch '>'  = "zg"
501 encode_ch '#'  = "zh"
502 encode_ch '.'  = "zi"
503 encode_ch '<'  = "zl"
504 encode_ch '-'  = "zm"
505 encode_ch '!'  = "zn"
506 encode_ch '+'  = "zp"
507 encode_ch '\'' = "zq"
508 encode_ch '\\' = "zr"
509 encode_ch '/'  = "zs"
510 encode_ch '*'  = "zt"
511 encode_ch '^'  = "zu"
512 encode_ch '%'  = "zv"
513 encode_ch c    = ['z', 'x', intToDigit hi, intToDigit lo]
514                where
515                  (hi,lo) = ord c `quotRem` 16
516 \end{code}
517
518 Decode is used for user printing.
519
520 \begin{code}
521 decodeFS :: FAST_STRING -> FAST_STRING
522 decodeFS fs = _PK_ (decode (_UNPK_ fs))
523
524 decode :: EncodedString -> UserString
525 decode [] = []
526 decode ('Z' : rest) = decode_escape rest
527 decode ('z' : rest) = decode_escape rest
528 decode (c   : rest) = c : decode rest
529
530 decode_escape :: EncodedString -> UserString
531
532 decode_escape ('Z' : rest) = 'Z' : decode rest
533 decode_escape ('C' : rest) = ':' : decode rest
534 decode_escape ('L' : rest) = '(' : decode rest
535 decode_escape ('R' : rest) = ')' : decode rest
536 decode_escape ('M' : rest) = '[' : decode rest
537 decode_escape ('N' : rest) = ']' : decode rest
538
539 decode_escape ('z' : rest) = 'z' : decode rest
540 decode_escape ('a' : rest) = '&' : decode rest
541 decode_escape ('b' : rest) = '|' : decode rest
542 decode_escape ('d' : rest) = '$' : decode rest
543 decode_escape ('e' : rest) = '=' : decode rest
544 decode_escape ('g' : rest) = '>' : decode rest
545 decode_escape ('h' : rest) = '#' : decode rest
546 decode_escape ('i' : rest) = '.' : decode rest
547 decode_escape ('l' : rest) = '<' : decode rest
548 decode_escape ('m' : rest) = '-' : decode rest
549 decode_escape ('n' : rest) = '!' : decode rest
550 decode_escape ('p' : rest) = '+' : decode rest
551 decode_escape ('q' : rest) = '\'' : decode rest
552 decode_escape ('r' : rest) = '\\' : decode rest
553 decode_escape ('s' : rest) = '/' : decode rest
554 decode_escape ('t' : rest) = '*' : decode rest
555 decode_escape ('u' : rest) = '^' : decode rest
556 decode_escape ('v' : rest) = '%' : decode rest
557 decode_escape ('x' : d1 : d2 : rest) = chr (digitToInt d1 * 16 + digitToInt d2)  : decode rest
558
559 -- Tuples are coded as Z23T
560 decode_escape (c : rest)
561   | isDigit c = go (digitToInt c) rest
562   where
563     go n (c : rest) | isDigit c = go (10*n + digitToInt c) rest
564     go n ('T' : rest)           = '(' : replicate n ',' ++ ')' : decode rest
565     go n other = pprPanic "decode_escape" (ppr n <+> text (c:rest))
566
567 decode_escape (c : rest) = pprTrace "decode_escape" (char c) (decode rest)
568 \end{code}
569
570
571 %************************************************************************
572 %*                                                                      *
573 n\subsection{Lexical categories}
574 %*                                                                      *
575 %************************************************************************
576
577 These functions test strings to see if they fit the lexical categories
578 defined in the Haskell report.
579
580 \begin{code}
581 isLexCon,   isLexVar,    isLexId,    isLexSym    :: FAST_STRING -> Bool
582 isLexConId, isLexConSym, isLexVarId, isLexVarSym :: FAST_STRING -> Bool
583
584 isLexCon cs = isLexConId  cs || isLexConSym cs
585 isLexVar cs = isLexVarId  cs || isLexVarSym cs
586
587 isLexId  cs = isLexConId  cs || isLexVarId  cs
588 isLexSym cs = isLexConSym cs || isLexVarSym cs
589
590 -------------
591
592 isLexConId cs                           -- Prefix type or data constructors
593   | _NULL_ cs        = False            --      e.g. "Foo", "[]", "(,)" 
594   | cs == SLIT("[]") = True
595   | c  == '('        = True     -- (), (,), (,,), ...
596   | otherwise        = isUpper c || isUpperISO c
597   where                                 
598     c = _HEAD_ cs
599
600 isLexVarId cs                           -- Ordinary prefix identifiers
601   | _NULL_ cs    = False                --      e.g. "x", "_x"
602   | otherwise    = isLower c || isLowerISO c || c == '_'
603   where
604     c = _HEAD_ cs
605
606 isLexConSym cs                          -- Infix type or data constructors
607   | _NULL_ cs   = False                 --      e.g. ":-:", ":", "->"
608   | otherwise   = c  == ':'
609                || cs == SLIT("->")
610   where
611     c = _HEAD_ cs
612
613 isLexVarSym cs                          -- Infix identifiers
614   | _NULL_ cs = False                   --      e.g. "+"
615   | otherwise = isSymbolASCII c
616              || isSymbolISO c
617   where
618     c = _HEAD_ cs
619
620 -------------
621 isSymbolASCII c = c `elem` "!#$%&*+./<=>?@\\^|~-"
622 isSymbolISO   c = ord c `elem` (0xd7 : 0xf7 : [0xa1 .. 0xbf])
623 isUpperISO    (C# c#) = c# `geChar#` '\xc0'# && c# `leChar#` '\xde'# && c# `neChar#` '\xd7'#
624         --0xc0 <= oc && oc <= 0xde && oc /= 0xd7 where oc = ord c
625 isLowerISO    (C# c#) = c# `geChar#` '\xdf'# && c# `leChar#` '\xff'# && c# `neChar#` '\xf7'#
626         --0xdf <= oc && oc <= 0xff && oc /= 0xf7 where oc = ord c
627 \end{code}