[project @ 2000-12-07 08:17:55 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, 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, 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                | 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 ipName   = IPName
103
104
105 nameSpaceString :: NameSpace -> String
106 nameSpaceString DataName  = "Data constructor"
107 nameSpaceString VarName   = "Variable"
108 nameSpaceString IPName    = "Implicit Param"
109 nameSpaceString TvName    = "Type variable"
110 nameSpaceString TcClsName = "Type constructor or class"
111 \end{code}
112
113
114 %************************************************************************
115 %*                                                                      *
116 \subsection[Name-pieces-datatypes]{The @OccName@ datatypes}
117 %*                                                                      *
118 %************************************************************************
119
120 \begin{code}
121 data OccName = OccName 
122                         NameSpace
123                         EncodedFS
124 \end{code}
125
126
127 \begin{code}
128 instance Eq OccName where
129     (OccName sp1 s1) == (OccName sp2 s2) = s1 == s2 && sp1 == sp2
130
131 instance Ord OccName where
132     compare (OccName sp1 s1) (OccName sp2 s2) = (s1  `compare` s2) `thenCmp`
133                                                 (sp1 `compare` sp2)
134 \end{code}
135
136
137 %************************************************************************
138 %*                                                                      *
139 \subsection{Printing}
140 %*                                                                      *
141 %************************************************************************
142  
143 \begin{code}
144 instance Outputable OccName where
145     ppr = pprOccName
146
147 pprOccName :: OccName -> SDoc
148 pprOccName (OccName sp occ) = pprEncodedFS occ
149 \end{code}
150
151
152 %************************************************************************
153 %*                                                                      *
154 \subsection{Construction}
155 %*                                                                      *
156 %************************************************************************
157
158 *Sys* things do no encoding; the caller should ensure that the thing is
159 already encoded
160
161 \begin{code}
162 mkSysOcc :: NameSpace -> EncodedString -> OccName
163 mkSysOcc occ_sp str = ASSERT2( alreadyEncoded str, text str )
164                       OccName occ_sp (_PK_ str)
165
166 mkSysOccFS :: NameSpace -> EncodedFS -> OccName
167 mkSysOccFS occ_sp fs = ASSERT2( alreadyEncodedFS fs, ppr fs )
168                        OccName occ_sp fs
169
170 mkCCallOcc :: EncodedString -> OccName
171 -- This version of mkSysOcc doesn't check that the string is already encoded,
172 -- because it will be something like "{__ccall f dyn Int# -> Int#}" 
173 -- This encodes a lot into something that then parses like an Id.
174 -- But then alreadyEncoded complains about the braces!
175 mkCCallOcc str = OccName varName (_PK_ str)
176
177 -- Kind constructors get a special function.  Uniquely, they are not encoded,
178 -- so that they have names like '*'.  This means that *even in interface files*
179 -- we'll get kinds like (* -> (* -> *)).  We can't use mkSysOcc because it
180 -- has an ASSERT that doesn't hold.
181 mkKindOccFS :: NameSpace -> EncodedFS -> OccName
182 mkKindOccFS occ_sp fs = OccName occ_sp fs
183 \end{code}
184
185 *Source-code* things are encoded.
186
187 \begin{code}
188 mkOccFS :: NameSpace -> UserFS -> OccName
189 mkOccFS occ_sp fs = mkSysOccFS occ_sp (encodeFS fs)
190
191 mkVarOcc :: UserFS -> OccName
192 mkVarOcc fs = mkSysOccFS varName (encodeFS fs)
193 \end{code}
194
195
196
197 %************************************************************************
198 %*                                                                      *
199 \subsection{Predicates and taking them apart}
200 %*                                                                      *
201 %************************************************************************
202
203 \begin{code} 
204 occNameFS :: OccName -> EncodedFS
205 occNameFS (OccName _ s) = s
206
207 occNameString :: OccName -> EncodedString
208 occNameString (OccName _ s) = _UNPK_ s
209
210 occNameUserString :: OccName -> UserString
211 occNameUserString occ = decode (occNameString occ)
212
213 occNameSpace :: OccName -> NameSpace
214 occNameSpace (OccName sp _) = sp
215
216 setOccNameSpace :: OccName -> NameSpace -> OccName
217 setOccNameSpace (OccName _ occ) sp = OccName sp occ
218
219 -- occNameFlavour is used only to generate good error messages
220 occNameFlavour :: OccName -> String
221 occNameFlavour (OccName sp _) = nameSpaceString sp
222 \end{code}
223
224 \begin{code}
225 isTvOcc, isDataSymOcc, isSymOcc :: OccName -> Bool
226
227 isTvOcc (OccName TvName _) = True
228 isTvOcc 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
247 isIPOcc (OccName IPName _) = True
248 isIPOcc _                  = False
249 \end{code}
250
251
252 %************************************************************************
253 %*                                                                      *
254 \subsection{Making system names}
255 %*                                                                      *
256 %************************************************************************
257
258 Here's our convention for splitting up the interface file name space:
259
260         d...            dictionary identifiers
261                         (local variables, so no name-clash worries)
262
263         $f...           dict-fun identifiers (from inst decls)
264         $dm...          default methods
265         $p...           superclass selectors
266         $w...           workers
267         $T...           compiler-generated tycons for dictionaries
268         $D...           ...ditto data cons
269         $sf..           specialised version of f
270
271         in encoded form these appear as Zdfxxx etc
272
273         :...            keywords (export:, letrec: etc.)
274
275 This knowledge is encoded in the following functions.
276
277
278 @mk_deriv@ generates an @OccName@ from the one-char prefix and a string.
279 NB: The string must already be encoded!
280
281 \begin{code}
282 mk_deriv :: NameSpace 
283          -> String              -- Distinguishes one sort of derived name from another
284          -> EncodedString       -- Must be already encoded!!  We don't want to encode it a 
285                                 -- second time because encoding isn't itempotent
286          -> OccName
287
288 mk_deriv occ_sp sys_prefix str = mkSysOcc occ_sp (encode sys_prefix ++ str)
289 \end{code}
290
291 \begin{code}
292 mkDictOcc, mkIPOcc, mkWorkerOcc, mkDefaultMethodOcc,
293            mkClassTyConOcc, mkClassDataConOcc, mkSpecOcc
294    :: OccName -> OccName
295
296 -- These derived variables have a prefix that no Haskell value could have
297 mkWorkerOcc        = mk_simple_deriv varName  "$w"
298 mkDefaultMethodOcc = mk_simple_deriv varName  "$dm"
299 mkDerivedTyConOcc  = mk_simple_deriv tcName   ":"       -- The : prefix makes sure it classifies
300 mkClassTyConOcc    = mk_simple_deriv tcName   ":T"      -- as a tycon/datacon
301 mkClassDataConOcc  = mk_simple_deriv dataName ":D"      --
302 mkDictOcc          = mk_simple_deriv varName  "$d"
303 mkIPOcc            = mk_simple_deriv varName  "$i"
304 mkSpecOcc          = mk_simple_deriv varName  "$s"
305 mkForeignExportOcc = mk_simple_deriv varName  "$f"
306 mkGenOcc1           = mk_simple_deriv varName  "$gfrom"      -- Generics
307 mkGenOcc2           = mk_simple_deriv varName  "$gto"        -- Generics
308 mk_simple_deriv sp px occ = mk_deriv sp px (occNameString occ)
309
310
311 isSysOcc ::  OccName -> Bool    -- True for all these '$' things
312 isSysOcc occ = case occNameUserString occ of
313                    ('$' : _ ) -> True
314                    other      -> False  -- We don't care about the ':' ones
315                                         -- isSysOcc is only called for Ids anyway
316 \end{code}
317
318 \begin{code}
319 mkSuperDictSelOcc :: Int        -- Index of superclass, eg 3
320                   -> OccName    -- Class, eg "Ord"
321                   -> OccName    -- eg "p3Ord"
322 mkSuperDictSelOcc index cls_occ
323   = mk_deriv varName "$p" (show index ++ occNameString cls_occ)
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
444         (,,,,)          Z4T     5-tuple
445         (#,,,,#)        Z4H     unboxed 5-tuple
446                 (NB: the number is one different to the number of 
447                 elements.  No real reason except that () is a zero-tuple,
448                 while (,) is a 2-tuple.)
449
450 \begin{code}
451 -- alreadyEncoded is used in ASSERTs to check for encoded
452 -- strings.  It isn't fail-safe, of course, because, say 'zh' might
453 -- be encoded or not.
454 alreadyEncoded :: String -> Bool
455 alreadyEncoded s = all ok s
456                  where
457                    ok ' ' = True
458                         -- This is a bit of a lie; if we really wanted spaces
459                         -- in names we'd have to encode them.  But we do put
460                         -- spaces in ccall "occurrences", and we don't want to
461                         -- reject them here
462                    ok ch  = ISALPHANUM ch
463
464 alreadyEncodedFS :: FAST_STRING -> Bool
465 alreadyEncodedFS fs = alreadyEncoded (_UNPK_ fs)
466
467 encode :: UserString -> EncodedString
468 encode cs = case maybe_tuple cs of
469                 Just n  -> n            -- Tuples go to Z2T etc
470                 Nothing -> go cs
471           where
472                 go []     = []
473                 go (c:cs) = encode_ch c ++ go cs
474
475 maybe_tuple ('(' : '#' : cs) = case count_commas (0::Int) cs of
476                                  (n, '#' : ')' : cs) -> Just ('Z' : shows n "H")
477                                  other               -> Nothing
478 maybe_tuple ('(' : cs)       = case count_commas (0::Int) cs of
479                                  (n, ')' : cs) -> Just ('Z' : shows n "T")
480                                  other         -> Nothing
481 maybe_tuple other            = Nothing
482
483 count_commas :: Int -> String -> (Int, String)
484 count_commas n (',' : cs) = count_commas (n+1) cs
485 count_commas n cs         = (n,cs)
486
487 encodeFS :: UserFS -> EncodedFS
488 encodeFS fast_str  | all unencodedChar str = fast_str
489                    | otherwise             = _PK_ (encode str)
490                    where
491                      str = _UNPK_ fast_str
492
493 unencodedChar :: Char -> Bool   -- True for chars that don't need encoding
494 unencodedChar 'Z' = False
495 unencodedChar 'z' = False
496 unencodedChar c   = ISALPHANUM c
497
498 encode_ch :: Char -> EncodedString
499 encode_ch c | unencodedChar c = [c]     -- Common case first
500
501 -- Constructors
502 encode_ch '('  = "ZL"   -- Needed for things like (,), and (->)
503 encode_ch ')'  = "ZR"   -- For symmetry with (
504 encode_ch '['  = "ZM"
505 encode_ch ']'  = "ZN"
506 encode_ch ':'  = "ZC"
507 encode_ch 'Z'  = "ZZ"
508
509 -- Variables
510 encode_ch 'z'  = "zz"
511 encode_ch '&'  = "za"
512 encode_ch '|'  = "zb"
513 encode_ch '^'  = "zc"
514 encode_ch '$'  = "zd"
515 encode_ch '='  = "ze"
516 encode_ch '>'  = "zg"
517 encode_ch '#'  = "zh"
518 encode_ch '.'  = "zi"
519 encode_ch '<'  = "zl"
520 encode_ch '-'  = "zm"
521 encode_ch '!'  = "zn"
522 encode_ch '+'  = "zp"
523 encode_ch '\'' = "zq"
524 encode_ch '\\' = "zr"
525 encode_ch '/'  = "zs"
526 encode_ch '*'  = "zt"
527 encode_ch '_'  = "zu"
528 encode_ch '%'  = "zv"
529 encode_ch c    = 'z' : shows (ord c) "U"
530 \end{code}
531
532 Decode is used for user printing.
533
534 \begin{code}
535 decodeFS :: FAST_STRING -> FAST_STRING
536 decodeFS fs = _PK_ (decode (_UNPK_ fs))
537
538 decode :: EncodedString -> UserString
539 decode [] = []
540 decode ('Z' : rest) = decode_escape rest
541 decode ('z' : rest) = decode_escape rest
542 decode (c   : rest) = c : decode rest
543
544 decode_escape :: EncodedString -> UserString
545
546 decode_escape ('L' : rest) = '(' : decode rest
547 decode_escape ('R' : rest) = ')' : decode rest
548 decode_escape ('M' : rest) = '[' : decode rest
549 decode_escape ('N' : rest) = ']' : decode rest
550 decode_escape ('C' : rest) = ':' : decode rest
551 decode_escape ('Z' : rest) = 'Z' : decode rest
552
553 decode_escape ('z' : rest) = 'z' : decode rest
554 decode_escape ('a' : rest) = '&' : decode rest
555 decode_escape ('b' : rest) = '|' : decode rest
556 decode_escape ('c' : rest) = '^' : decode rest
557 decode_escape ('d' : rest) = '$' : decode rest
558 decode_escape ('e' : rest) = '=' : decode rest
559 decode_escape ('g' : rest) = '>' : decode rest
560 decode_escape ('h' : rest) = '#' : decode rest
561 decode_escape ('i' : rest) = '.' : decode rest
562 decode_escape ('l' : rest) = '<' : decode rest
563 decode_escape ('m' : rest) = '-' : decode rest
564 decode_escape ('n' : rest) = '!' : decode rest
565 decode_escape ('p' : rest) = '+' : decode rest
566 decode_escape ('q' : rest) = '\'' : decode rest
567 decode_escape ('r' : rest) = '\\' : decode rest
568 decode_escape ('s' : rest) = '/' : decode rest
569 decode_escape ('t' : rest) = '*' : decode rest
570 decode_escape ('u' : rest) = '_' : decode rest
571 decode_escape ('v' : rest) = '%' : decode rest
572
573 -- Tuples are coded as Z23T
574 -- Characters not having a specific code are coded as z224U
575 decode_escape (c : rest)
576   | isDigit c = go (digitToInt c) rest
577   where
578     go n (c : rest) | isDigit c = go (10*n + digitToInt c) rest
579     go n ('T' : rest)           = '(' : replicate n ',' ++ ')' : decode rest
580     go n ('H' : rest)           = '(' : '#' : replicate n ',' ++ '#' : ')' : decode rest
581     go n ('U' : rest)           = chr n : decode rest
582     go n other = pprPanic "decode_escape" (ppr n <+> text (c:rest))
583
584 decode_escape (c : rest) = pprTrace "decode_escape" (char c) (decode rest)
585 \end{code}
586
587
588 %************************************************************************
589 %*                                                                      *
590 n\subsection{Lexical categories}
591 %*                                                                      *
592 %************************************************************************
593
594 These functions test strings to see if they fit the lexical categories
595 defined in the Haskell report.
596
597 \begin{code}
598 isLexCon,   isLexVar,    isLexId,    isLexSym    :: FAST_STRING -> Bool
599 isLexConId, isLexConSym, isLexVarId, isLexVarSym :: FAST_STRING -> Bool
600
601 isLexCon cs = isLexConId  cs || isLexConSym cs
602 isLexVar cs = isLexVarId  cs || isLexVarSym cs
603
604 isLexId  cs = isLexConId  cs || isLexVarId  cs
605 isLexSym cs = isLexConSym cs || isLexVarSym cs
606
607 -------------
608
609 isLexConId cs                           -- Prefix type or data constructors
610   | _NULL_ cs        = False            --      e.g. "Foo", "[]", "(,)" 
611   | cs == SLIT("[]") = True
612   | otherwise        = startsConId (_HEAD_ cs)
613
614 isLexVarId cs                           -- Ordinary prefix identifiers
615   | _NULL_ cs    = False                --      e.g. "x", "_x"
616   | otherwise    = startsVarId (_HEAD_ cs)
617
618 isLexConSym cs                          -- Infix type or data constructors
619   | _NULL_ cs   = False                 --      e.g. ":-:", ":", "->"
620   | cs == SLIT("->") = True
621   | otherwise   = startsConSym (_HEAD_ cs)
622
623 isLexVarSym cs                          -- Infix identifiers
624   | _NULL_ cs = False                   --      e.g. "+"
625   | otherwise = startsVarSym (_HEAD_ cs)
626
627 -------------
628 startsVarSym, startsVarId, startsConSym, startsConId :: Char -> Bool
629 startsVarSym c = isSymbolASCII c || isSymbolISO c       -- Infix Ids
630 startsConSym c = c == ':'                               -- Infix data constructors
631 startsVarId c  = isLower c || isLowerISO c || c == '_'  -- Ordinary Ids
632 startsConId c  = isUpper c || isUpperISO c || c == '('  -- Ordinary type constructors and data constructors
633
634
635 isSymbolASCII c = c `elem` "!#$%&*+./<=>?@\\^|~-"
636 isSymbolISO   c = ord c `elem` (0xd7 : 0xf7 : [0xa1 .. 0xbf])
637 isUpperISO    (C# c#) = c# `geChar#` '\xc0'# && c# `leChar#` '\xde'# && c# `neChar#` '\xd7'#
638         --0xc0 <= oc && oc <= 0xde && oc /= 0xd7 where oc = ord c
639 isLowerISO    (C# c#) = c# `geChar#` '\xdf'# && c# `leChar#` '\xff'# && c# `neChar#` '\xf7'#
640         --0xdf <= oc && oc <= 0xff && oc /= 0xf7 where oc = ord c
641 \end{code}