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