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