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