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