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