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