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