[project @ 2000-06-09 07:32:31 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         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 = ptext fs
70 \end{code}
71
72 %************************************************************************
73 %*                                                                      *
74 \subsection{Name space}
75 %*                                                                      *
76 %************************************************************************
77
78 \begin{code}
79 data NameSpace = VarName        -- Variables
80                | IPName         -- Implicit Parameters
81                | DataName       -- Data constructors
82                | TvName         -- Type variables
83                | UvName         -- Usage variables
84                | TcClsName      -- Type constructors and classes; Haskell has them
85                                 -- in the same name space for now.
86                deriving( Eq, Ord )
87
88 -- Though type constructors and classes are in the same name space now,
89 -- the NameSpace type is abstract, so we can easily separate them later
90 tcName    = TcClsName           -- Type constructors
91 clsName   = TcClsName           -- Classes
92 tcClsName = TcClsName           -- Not sure which!
93
94 dataName = DataName
95 tvName   = TvName
96 uvName   = UvName
97 varName  = VarName
98 ipName   = IPName
99
100
101 nameSpaceString :: NameSpace -> String
102 nameSpaceString DataName  = "Data constructor"
103 nameSpaceString VarName   = "Variable"
104 nameSpaceString IPName    = "Implicit Param"
105 nameSpaceString TvName    = "Type variable"
106 nameSpaceString UvName    = "Usage variable"
107 nameSpaceString TcClsName = "Type constructor or class"
108 \end{code}
109
110
111 %************************************************************************
112 %*                                                                      *
113 \subsection[Name-pieces-datatypes]{The @OccName@ datatypes}
114 %*                                                                      *
115 %************************************************************************
116
117 \begin{code}
118 data OccName = OccName 
119                         NameSpace
120                         EncodedFS
121 \end{code}
122
123
124 \begin{code}
125 instance Eq OccName where
126     (OccName sp1 s1) == (OccName sp2 s2) = s1 == s2 && sp1 == sp2
127
128 instance Ord OccName where
129     compare (OccName sp1 s1) (OccName sp2 s2) = (s1  `compare` s2) `thenCmp`
130                                                 (sp1 `compare` sp2)
131 \end{code}
132
133
134 %************************************************************************
135 %*                                                                      *
136 \subsection{Printing}
137 %*                                                                      *
138 %************************************************************************
139  
140 \begin{code}
141 instance Outputable OccName where
142     ppr = pprOccName
143
144 pprOccName :: OccName -> SDoc
145 pprOccName (OccName sp occ) = pprEncodedFS occ
146 \end{code}
147
148
149 %************************************************************************
150 %*                                                                      *
151 \subsection{Construction}
152 %*                                                                      *
153 %************************************************************************
154
155 *Sys* things do no encoding; the caller should ensure that the thing is
156 already encoded
157
158 \begin{code}
159 mkSysOcc :: NameSpace -> EncodedString -> OccName
160 mkSysOcc occ_sp str = ASSERT2( alreadyEncoded str, text str )
161                       OccName occ_sp (_PK_ str)
162
163 mkSysOccFS :: NameSpace -> EncodedFS -> OccName
164 mkSysOccFS occ_sp fs = ASSERT2( alreadyEncodedFS fs, ppr fs )
165                        OccName occ_sp fs
166
167 mkCCallOcc :: EncodedString -> OccName
168 -- This version of mkSysOcc doesn't check that the string is already encoded,
169 -- because it will be something like "{__ccall f dyn Int# -> Int#}" 
170 -- This encodes a lot into something that then parses like an Id.
171 -- But then alreadyEncoded complains about the braces!
172 mkCCallOcc str = OccName varName (_PK_ str)
173
174 -- Kind constructors get a speical function.  Uniquely, they are not encoded,
175 -- so that they have names like '*'.  This means that *even in interface files*
176 -- we'll get kinds like (* -> (* -> *)).  We can't use mkSysOcc because it
177 -- has an ASSERT that doesn't hold.
178 mkKindOccFS :: NameSpace -> EncodedFS -> OccName
179 mkKindOccFS occ_sp fs = OccName occ_sp fs
180 \end{code}
181
182 *Source-code* things are encoded.
183
184 \begin{code}
185 mkSrcOccFS :: NameSpace -> UserFS -> OccName
186 mkSrcOccFS occ_sp fs = mkSysOccFS occ_sp (encodeFS fs)
187
188 mkSrcVarOcc :: UserFS -> OccName
189 mkSrcVarOcc fs = mkSysOccFS varName (encodeFS fs)
190 \end{code}
191
192
193
194 %************************************************************************
195 %*                                                                      *
196 \subsection{Predicates and taking them apart}
197 %*                                                                      *
198 %************************************************************************
199
200 \begin{code} 
201 occNameFS :: OccName -> EncodedFS
202 occNameFS (OccName _ s) = s
203
204 occNameString :: OccName -> EncodedString
205 occNameString (OccName _ s) = _UNPK_ s
206
207 occNameUserString :: OccName -> UserString
208 occNameUserString occ = decode (occNameString occ)
209
210 occNameSpace :: OccName -> NameSpace
211 occNameSpace (OccName sp _) = sp
212
213 setOccNameSpace :: OccName -> NameSpace -> OccName
214 setOccNameSpace (OccName _ occ) sp = OccName sp occ
215
216 -- occNameFlavour is used only to generate good error messages
217 occNameFlavour :: OccName -> String
218 occNameFlavour (OccName sp _) = nameSpaceString sp
219 \end{code}
220
221 \begin{code}
222 isTvOcc, isDataSymOcc, isSymOcc, isUvOcc :: OccName -> Bool
223
224 isTvOcc (OccName TvName _) = True
225 isTvOcc other              = False
226
227 isUvOcc (OccName UvName _) = True
228 isUvOcc 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
307 mk_simple_deriv sp px occ = mk_deriv sp px (occNameString occ)
308
309
310 isSysOcc ::  OccName -> Bool    -- True for all these '$' things
311 isSysOcc occ = case occNameUserString occ of
312                    ('$' : _ ) -> True
313                    other      -> False  -- We don't care about the ':' ones
314                                         -- isSysOcc is only called for Ids anyway
315 \end{code}
316
317 \begin{code}
318 mkSuperDictSelOcc :: Int        -- Index of superclass, eg 3
319                   -> OccName    -- Class, eg "Ord"
320                   -> OccName    -- eg "p3Ord"
321 mkSuperDictSelOcc index cls_occ
322   = mk_deriv varName "$p" (show index ++ occNameString cls_occ)
323 \end{code}
324
325
326 \begin{code}
327 mkDFunOcc :: EncodedString      -- Typically the class and type glommed together e.g. "OrdMaybe"
328           -> Int                -- Unique to distinguish dfuns which share the previous two
329                                 --      eg 3
330           -- The requirement is that the (string,index) pair be unique in this module
331
332           -> OccName    -- "$fOrdMaybe3"
333
334 mkDFunOcc string index
335   = mk_deriv VarName "$f" (show_index ++ string)
336   where
337     show_index | index == 0 = ""
338                | otherwise  = show index
339 \end{code}
340
341 We used to add a '$m' to indicate a method, but that gives rise to bad
342 error messages from the type checker when we print the function name or pattern
343 of an instance-decl binding.  Why? Because the binding is zapped
344 to use the method name in place of the selector name.
345 (See TcClassDcl.tcMethodBind)
346
347 The way it is now, -ddump-xx output may look confusing, but
348 you can always say -dppr-debug to get the uniques.
349
350 However, we *do* have to zap the first character to be lower case,
351 because overloaded constructors (blarg) generate methods too.
352 And convert to VarName space
353
354 e.g. a call to constructor MkFoo where
355         data (Ord a) => Foo a = MkFoo a
356
357 If this is necessary, we do it by prefixing '$m'.  These 
358 guys never show up in error messages.  What a hack.
359
360 \begin{code}
361 mkMethodOcc :: OccName -> OccName
362 mkMethodOcc occ@(OccName VarName fs) = occ
363 mkMethodOcc occ                      = mk_simple_deriv varName "$m" occ
364 \end{code}
365
366
367 %************************************************************************
368 %*                                                                      *
369 \subsection{Tidying them up}
370 %*                                                                      *
371 %************************************************************************
372
373 Before we print chunks of code we like to rename it so that
374 we don't have to print lots of silly uniques in it.  But we mustn't
375 accidentally introduce name clashes!  So the idea is that we leave the
376 OccName alone unless it accidentally clashes with one that is already
377 in scope; if so, we tack on '1' at the end and try again, then '2', and
378 so on till we find a unique one.
379
380 There's a wrinkle for operators.  Consider '>>='.  We can't use '>>=1' 
381 because that isn't a single lexeme.  So we encode it to 'lle' and *then*
382 tack on the '1', if necessary.
383
384 \begin{code}
385 type TidyOccEnv = FiniteMap FAST_STRING Int     -- The in-scope OccNames
386 emptyTidyOccEnv = emptyFM
387
388 initTidyOccEnv :: [OccName] -> TidyOccEnv       -- Initialise with names to avoid!
389 initTidyOccEnv = foldl (\env (OccName _ fs) -> addToFM env fs 1) emptyTidyOccEnv
390
391 tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName)
392
393 tidyOccName in_scope occ@(OccName occ_sp fs)
394   | not (fs `elemFM` in_scope)
395   = (addToFM in_scope fs 1, occ)        -- First occurrence
396
397   | otherwise                           -- Already occurs
398   = go in_scope (_UNPK_ fs)
399   where
400
401     go in_scope str = case lookupFM in_scope pk_str of
402                         Just n  -> go (addToFM in_scope pk_str (n+1)) (str ++ show n)
403                                 -- Need to go round again, just in case "t3" (say) 
404                                 -- clashes with a "t3" that's already in scope
405
406                         Nothing -> (addToFM in_scope pk_str 1, mkSysOccFS occ_sp pk_str)
407                                 -- str is now unique
408                     where
409                       pk_str = _PK_ str
410 \end{code}
411
412
413 %************************************************************************
414 %*                                                                      *
415 \subsection{The 'Z' encoding}
416 %*                                                                      *
417 %************************************************************************
418
419 This is the main name-encoding and decoding function.  It encodes any
420 string into a string that is acceptable as a C name.  This is the name
421 by which things are known right through the compiler.
422
423 The basic encoding scheme is this.  
424
425 * Tuples (,,,) are coded as Z3T
426
427 * Alphabetic characters (upper and lower) and digits
428         all translate to themselves; 
429         except 'Z', which translates to 'ZZ'
430         and    'z', which translates to 'zz'
431   We need both so that we can preserve the variable/tycon distinction
432
433 * Most other printable characters translate to 'zx' or 'Zx' for some
434         alphabetic character x
435
436 * The others translate as 'zxdd' where 'dd' is exactly two hexadecimal
437         digits for the ord of the character
438
439         Before          After
440         --------------------------
441         Trak            Trak
442         foo_wib         foozuwib
443         >               zg
444         >1              zg1
445         foo#            foozh
446         foo##           foozhzh
447         foo##1          foozhzh1
448         fooZ            fooZZ   
449         :+              Zczp
450         ()              Z0T
451         (,,,,)          Z4T
452
453
454 \begin{code}
455 -- alreadyEncoded is used in ASSERTs to check for encoded
456 -- strings.  It isn't fail-safe, of course, because, say 'zh' might
457 -- be encoded or not.
458 alreadyEncoded :: String -> Bool
459 alreadyEncoded s = all ok s
460                  where
461                    ok ' ' = True                -- This is a bit of a lie; if we really wanted spaces
462                                                 -- in names we'd have to encode them.  But we do put
463                                                 -- spaces in ccall "occurrences", and we don't want to
464                                                 -- reject them here
465                    ok ch  = ISALPHANUM ch
466
467 alreadyEncodedFS :: FAST_STRING -> Bool
468 alreadyEncodedFS fs = alreadyEncoded (_UNPK_ fs)
469
470 encode :: UserString -> EncodedString
471 encode cs = case maybe_tuple cs of
472                 Just n  -> 'Z' : show n ++ "T"          -- Tuples go to Z2T etc
473                 Nothing -> go cs
474           where
475                 go []     = []
476                 go (c:cs) = encode_ch c ++ go cs
477
478 -- ToDo: Unboxed tuples too, perhaps?
479 maybe_tuple ('(' : cs) = check_tuple (0::Int) cs
480 maybe_tuple other      = Nothing
481
482 check_tuple :: Int -> String -> Maybe Int
483 check_tuple n (',' : cs) = check_tuple (n+1) cs
484 check_tuple n ")"        = Just n
485 check_tuple n other      = Nothing
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', 'x', intToDigit hi, intToDigit lo]
530                where
531                  (hi,lo) = ord c `quotRem` 16
532 \end{code}
533
534 Decode is used for user printing.
535
536 \begin{code}
537 decodeFS :: FAST_STRING -> FAST_STRING
538 decodeFS fs = _PK_ (decode (_UNPK_ fs))
539
540 decode :: EncodedString -> UserString
541 decode [] = []
542 decode ('Z' : rest) = decode_escape rest
543 decode ('z' : rest) = decode_escape rest
544 decode (c   : rest) = c : decode rest
545
546 decode_escape :: EncodedString -> UserString
547
548 decode_escape ('L' : rest) = '(' : decode rest
549 decode_escape ('R' : rest) = ')' : decode rest
550 decode_escape ('M' : rest) = '[' : decode rest
551 decode_escape ('N' : rest) = ']' : decode rest
552 decode_escape ('C' : rest) = ':' : decode rest
553 decode_escape ('Z' : rest) = 'Z' : decode rest
554
555 decode_escape ('z' : rest) = 'z' : decode rest
556 decode_escape ('a' : rest) = '&' : decode rest
557 decode_escape ('b' : rest) = '|' : decode rest
558 decode_escape ('c' : rest) = '^' : decode rest
559 decode_escape ('d' : rest) = '$' : decode rest
560 decode_escape ('e' : rest) = '=' : decode rest
561 decode_escape ('g' : rest) = '>' : decode rest
562 decode_escape ('h' : rest) = '#' : decode rest
563 decode_escape ('i' : rest) = '.' : decode rest
564 decode_escape ('l' : rest) = '<' : decode rest
565 decode_escape ('m' : rest) = '-' : decode rest
566 decode_escape ('n' : rest) = '!' : decode rest
567 decode_escape ('p' : rest) = '+' : decode rest
568 decode_escape ('q' : rest) = '\'' : decode rest
569 decode_escape ('r' : rest) = '\\' : decode rest
570 decode_escape ('s' : rest) = '/' : decode rest
571 decode_escape ('t' : rest) = '*' : decode rest
572 decode_escape ('u' : rest) = '_' : decode rest
573 decode_escape ('v' : rest) = '%' : decode rest
574 decode_escape ('x' : d1 : d2 : rest) = chr (digitToInt d1 * 16 + digitToInt d2)  : decode rest
575
576 -- Tuples are coded as Z23T
577 decode_escape (c : rest)
578   | isDigit c = go (digitToInt c) rest
579   where
580     go n (c : rest) | isDigit c = go (10*n + digitToInt c) rest
581     go n ('T' : rest)           = '(' : replicate 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}