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