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