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