Module header tidyup, phase 1
[ghc-hetmet.git] / compiler / basicTypes / OccName.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 %
5
6 \begin{code}
7 module OccName (
8         -- * The NameSpace type; abstact
9         NameSpace, tcName, clsName, tcClsName, dataName, varName, 
10         tvName, srcDataName,
11
12         -- ** Printing
13         pprNameSpace, pprNonVarNameSpace, pprNameSpaceBrief,
14
15         -- * The OccName type
16         OccName,        -- Abstract, instance of Outputable
17         pprOccName, 
18
19         -- ** Construction      
20         mkOccName, mkOccNameFS, 
21         mkVarOcc, mkVarOccFS,
22         mkTyVarOcc,
23         mkDFunOcc,
24         mkTupleOcc, 
25         setOccNameSpace,
26
27         -- ** Derived OccNames
28         mkDataConWrapperOcc, mkWorkerOcc, mkDefaultMethodOcc,
29         mkDerivedTyConOcc, mkNewTyCoOcc,
30         mkClassTyConOcc, mkClassDataConOcc, mkDictOcc, mkIPOcc, 
31         mkSpecOcc, mkForeignExportOcc, mkGenOcc1, mkGenOcc2,
32         mkDataTOcc, mkDataCOcc, mkDataConWorkerOcc,
33         mkSuperDictSelOcc, mkLocalOcc, mkMethodOcc, mkInstTyTcOcc,
34         mkInstTyCoOcc, 
35
36         -- ** Deconstruction
37         occNameFS, occNameString, occNameSpace, 
38
39         isVarOcc, isTvOcc, isTcOcc, isDataOcc, isDataSymOcc, isSymOcc, isValOcc,
40         parenSymOcc, reportIfUnused, isTcClsName, isVarName,
41
42         isTupleOcc_maybe,
43
44         -- The OccEnv type
45         OccEnv, emptyOccEnv, unitOccEnv, extendOccEnv, mapOccEnv,
46         lookupOccEnv, mkOccEnv, extendOccEnvList, elemOccEnv,
47         occEnvElts, foldOccEnv, plusOccEnv, plusOccEnv_C, extendOccEnv_C,
48
49         -- The OccSet type
50         OccSet, emptyOccSet, unitOccSet, mkOccSet, extendOccSet, 
51         extendOccSetList,
52         unionOccSets, unionManyOccSets, minusOccSet, elemOccSet, occSetElts, 
53         foldOccSet, isEmptyOccSet, intersectOccSet, intersectsOccSet,
54
55         -- Tidying up
56         TidyOccEnv, emptyTidyOccEnv, tidyOccName, initTidyOccEnv,
57
58         -- The basic form of names
59         isLexCon, isLexVar, isLexId, isLexSym,
60         isLexConId, isLexConSym, isLexVarId, isLexVarSym,
61         startsVarSym, startsVarId, startsConSym, startsConId
62     ) where
63
64 #include "HsVersions.h"
65
66 import Util
67 import Unique
68 import BasicTypes
69 import StaticFlags
70 import UniqFM
71 import UniqSet
72 import FastString
73 import Outputable
74 import Binary
75
76 import GHC.Exts
77 import Data.Char
78
79 -- Unicode TODO: put isSymbol in libcompat
80 #if __GLASGOW_HASKELL__ > 604
81 import Data.Char        ( isSymbol )
82 #else
83 isSymbol = const False
84 #endif
85
86 \end{code}
87
88 %************************************************************************
89 %*                                                                      *
90 \subsection{Name space}
91 %*                                                                      *
92 %************************************************************************
93
94 \begin{code}
95 data NameSpace = VarName        -- Variables, including "source" data constructors
96                | DataName       -- "Real" data constructors 
97                | TvName         -- Type variables
98                | TcClsName      -- Type constructors and classes; Haskell has them
99                                 -- in the same name space for now.
100                deriving( Eq, Ord )
101    {-! derive: Binary !-}
102
103 -- Note [Data Constructors]  
104 -- see also: Note [Data Constructor Naming] in DataCon.lhs
105 -- 
106 --      "Source" data constructors are the data constructors mentioned
107 --      in Haskell source code
108 --
109 --      "Real" data constructors are the data constructors of the
110 --      representation type, which may not be the same as the source
111 --      type
112
113 -- Example:
114 --      data T = T !(Int,Int)
115 --
116 -- The source datacon has type (Int,Int) -> T
117 -- The real   datacon has type Int -> Int -> T
118 -- GHC chooses a representation based on the strictness etc.
119
120
121 -- Though type constructors and classes are in the same name space now,
122 -- the NameSpace type is abstract, so we can easily separate them later
123 tcName    = TcClsName           -- Type constructors
124 clsName   = TcClsName           -- Classes
125 tcClsName = TcClsName           -- Not sure which!
126
127 dataName    = DataName
128 srcDataName = DataName  -- Haskell-source data constructors should be
129                         -- in the Data name space
130
131 tvName      = TvName
132 varName     = VarName
133
134 isTcClsName :: NameSpace -> Bool
135 isTcClsName TcClsName = True
136 isTcClsName _         = False
137
138 isVarName :: NameSpace -> Bool  -- Variables or type variables, but not constructors
139 isVarName TvName  = True
140 isVarName VarName = True
141 isVarName other   = False
142
143 pprNameSpace :: NameSpace -> SDoc
144 pprNameSpace DataName  = ptext SLIT("data constructor")
145 pprNameSpace VarName   = ptext SLIT("variable")
146 pprNameSpace TvName    = ptext SLIT("type variable")
147 pprNameSpace TcClsName = ptext SLIT("type constructor or class")
148
149 pprNonVarNameSpace :: NameSpace -> SDoc
150 pprNonVarNameSpace VarName = empty
151 pprNonVarNameSpace ns = pprNameSpace ns
152
153 pprNameSpaceBrief DataName  = char 'd'
154 pprNameSpaceBrief VarName   = char 'v'
155 pprNameSpaceBrief TvName    = ptext SLIT("tv")
156 pprNameSpaceBrief TcClsName = ptext SLIT("tc")
157 \end{code}
158
159
160 %************************************************************************
161 %*                                                                      *
162 \subsection[Name-pieces-datatypes]{The @OccName@ datatypes}
163 %*                                                                      *
164 %************************************************************************
165
166 \begin{code}
167 data OccName = OccName 
168     { occNameSpace  :: !NameSpace
169     , occNameFS     :: !FastString
170     }
171 \end{code}
172
173
174 \begin{code}
175 instance Eq OccName where
176     (OccName sp1 s1) == (OccName sp2 s2) = s1 == s2 && sp1 == sp2
177
178 instance Ord OccName where
179     compare (OccName sp1 s1) (OccName sp2 s2) = (s1  `compare` s2) `thenCmp`
180                                                 (sp1 `compare` sp2)
181 \end{code}
182
183
184 %************************************************************************
185 %*                                                                      *
186 \subsection{Printing}
187 %*                                                                      *
188 %************************************************************************
189  
190 \begin{code}
191 instance Outputable OccName where
192     ppr = pprOccName
193
194 pprOccName :: OccName -> SDoc
195 pprOccName (OccName sp occ) 
196   = getPprStyle $ \ sty ->
197     if codeStyle sty 
198         then ftext (zEncodeFS occ)
199         else ftext occ <> if debugStyle sty 
200                             then braces (pprNameSpaceBrief sp)
201                             else empty
202 \end{code}
203
204
205 %************************************************************************
206 %*                                                                      *
207 \subsection{Construction}
208 %*                                                                      *
209 %************************************************************************
210
211 \begin{code}
212 mkOccName :: NameSpace -> String -> OccName
213 mkOccName occ_sp str = OccName occ_sp (mkFastString str)
214
215 mkOccNameFS :: NameSpace -> FastString -> OccName
216 mkOccNameFS occ_sp fs = OccName occ_sp fs
217
218 mkVarOcc :: String -> OccName
219 mkVarOcc s = mkOccName varName s
220
221 mkVarOccFS :: FastString -> OccName
222 mkVarOccFS fs = mkOccNameFS varName fs
223
224 mkTyVarOcc :: FastString -> OccName
225 mkTyVarOcc fs = mkOccNameFS tvName fs
226 \end{code}
227
228
229 %************************************************************************
230 %*                                                                      *
231                 Environments
232 %*                                                                      *
233 %************************************************************************
234
235 OccEnvs are used mainly for the envts in ModIfaces.
236
237 They are efficient, because FastStrings have unique Int# keys.  We assume
238 this key is less than 2^24, so we can make a Unique using
239         mkUnique ns key  :: Unique
240 where 'ns' is a Char reprsenting the name space.  This in turn makes it
241 easy to build an OccEnv.
242
243 \begin{code}
244 instance Uniquable OccName where
245   getUnique (OccName ns fs)
246       = mkUnique char (I# (uniqueOfFS fs))
247       where     -- See notes above about this getUnique function
248         char = case ns of
249                 VarName   -> 'i'
250                 DataName  -> 'd'
251                 TvName    -> 'v'
252                 TcClsName -> 't'
253
254 type OccEnv a = UniqFM a
255
256 emptyOccEnv :: OccEnv a
257 unitOccEnv  :: OccName -> a -> OccEnv a
258 extendOccEnv :: OccEnv a -> OccName -> a -> OccEnv a
259 extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a
260 lookupOccEnv :: OccEnv a -> OccName -> Maybe a
261 mkOccEnv     :: [(OccName,a)] -> OccEnv a
262 elemOccEnv   :: OccName -> OccEnv a -> Bool
263 foldOccEnv   :: (a -> b -> b) -> b -> OccEnv a -> b
264 occEnvElts   :: OccEnv a -> [a]
265 extendOccEnv_C :: (a->a->a) -> OccEnv a -> OccName -> a -> OccEnv a
266 plusOccEnv     :: OccEnv a -> OccEnv a -> OccEnv a
267 plusOccEnv_C   :: (a->a->a) -> OccEnv a -> OccEnv a -> OccEnv a
268 mapOccEnv      :: (a->b) -> OccEnv a -> OccEnv b
269
270 emptyOccEnv      = emptyUFM
271 unitOccEnv       = unitUFM
272 extendOccEnv     = addToUFM
273 extendOccEnvList = addListToUFM
274 lookupOccEnv     = lookupUFM
275 mkOccEnv         = listToUFM
276 elemOccEnv       = elemUFM
277 foldOccEnv       = foldUFM
278 occEnvElts       = eltsUFM
279 plusOccEnv       = plusUFM
280 plusOccEnv_C     = plusUFM_C
281 extendOccEnv_C   = addToUFM_C
282 mapOccEnv        = mapUFM
283
284 type OccSet = UniqFM OccName
285
286 emptyOccSet       :: OccSet
287 unitOccSet        :: OccName -> OccSet
288 mkOccSet          :: [OccName] -> OccSet
289 extendOccSet      :: OccSet -> OccName -> OccSet
290 extendOccSetList  :: OccSet -> [OccName] -> OccSet
291 unionOccSets      :: OccSet -> OccSet -> OccSet
292 unionManyOccSets  :: [OccSet] -> OccSet
293 minusOccSet       :: OccSet -> OccSet -> OccSet
294 elemOccSet        :: OccName -> OccSet -> Bool
295 occSetElts        :: OccSet -> [OccName]
296 foldOccSet        :: (OccName -> b -> b) -> b -> OccSet -> b
297 isEmptyOccSet     :: OccSet -> Bool
298 intersectOccSet   :: OccSet -> OccSet -> OccSet
299 intersectsOccSet  :: OccSet -> OccSet -> Bool
300
301 emptyOccSet       = emptyUniqSet
302 unitOccSet        = unitUniqSet
303 mkOccSet          = mkUniqSet
304 extendOccSet      = addOneToUniqSet
305 extendOccSetList  = addListToUniqSet
306 unionOccSets      = unionUniqSets
307 unionManyOccSets  = unionManyUniqSets
308 minusOccSet       = minusUniqSet
309 elemOccSet        = elementOfUniqSet
310 occSetElts        = uniqSetToList
311 foldOccSet        = foldUniqSet
312 isEmptyOccSet     = isEmptyUniqSet
313 intersectOccSet   = intersectUniqSets
314 intersectsOccSet s1 s2 = not (isEmptyOccSet (s1 `intersectOccSet` s2))
315 \end{code}
316
317
318 %************************************************************************
319 %*                                                                      *
320 \subsection{Predicates and taking them apart}
321 %*                                                                      *
322 %************************************************************************
323
324 \begin{code}
325 occNameString :: OccName -> String
326 occNameString (OccName _ s) = unpackFS s
327
328 setOccNameSpace :: NameSpace -> OccName -> OccName
329 setOccNameSpace sp (OccName _ occ) = OccName sp occ
330
331 isVarOcc, isTvOcc, isDataSymOcc, isSymOcc, isTcOcc :: OccName -> Bool
332
333 isVarOcc (OccName VarName _) = True
334 isVarOcc other               = False
335
336 isTvOcc (OccName TvName _) = True
337 isTvOcc other              = False
338
339 isTcOcc (OccName TcClsName _) = True
340 isTcOcc other                 = False
341
342 isValOcc (OccName VarName  _) = True
343 isValOcc (OccName DataName _) = True
344 isValOcc other                = False
345
346 -- Data constructor operator (starts with ':', or '[]')
347 -- Pretty inefficient!
348 isDataSymOcc (OccName DataName s) = isLexConSym s
349 isDataSymOcc (OccName VarName s)  
350   | isLexConSym s = pprPanic "isDataSymOcc: check me" (ppr s)
351                 -- Jan06: I don't think this should happen
352 isDataSymOcc other                = False
353
354 isDataOcc (OccName DataName _) = True
355 isDataOcc (OccName VarName s)  
356   | isLexCon s = pprPanic "isDataOcc: check me" (ppr s)
357                 -- Jan06: I don't think this should happen
358 isDataOcc other                = False
359
360 -- Any operator (data constructor or variable)
361 -- Pretty inefficient!
362 isSymOcc (OccName DataName s)  = isLexConSym s
363 isSymOcc (OccName TcClsName s) = isLexConSym s
364 isSymOcc (OccName VarName s)   = isLexSym s
365 isSymOcc other                 = False
366
367 parenSymOcc :: OccName -> SDoc -> SDoc
368 -- Wrap parens around an operator
369 parenSymOcc occ doc | isSymOcc occ = parens doc
370                     | otherwise    = doc
371 \end{code}
372
373
374 \begin{code}
375 reportIfUnused :: OccName -> Bool
376   -- Haskell 98 encourages compilers to suppress warnings about
377   -- unused names in a pattern if they start with "_".
378 reportIfUnused occ = case occNameString occ of
379                         ('_' : _) -> False
380                         _other    -> True
381 \end{code}
382
383
384 %************************************************************************
385 %*                                                                      *
386 \subsection{Making system names}
387 %*                                                                      *
388 %************************************************************************
389
390 Here's our convention for splitting up the interface file name space:
391
392         d...            dictionary identifiers
393                         (local variables, so no name-clash worries)
394
395         $f...           dict-fun identifiers (from inst decls)
396         $dm...          default methods
397         $p...           superclass selectors
398         $w...           workers
399         :T...           compiler-generated tycons for dictionaries
400         :D...           ...ditto data cons
401         $sf..           specialised version of f
402
403         in encoded form these appear as Zdfxxx etc
404
405         :...            keywords (export:, letrec: etc.)
406 --- I THINK THIS IS WRONG!
407
408 This knowledge is encoded in the following functions.
409
410
411 @mk_deriv@ generates an @OccName@ from the prefix and a string.
412 NB: The string must already be encoded!
413
414 \begin{code}
415 mk_deriv :: NameSpace 
416          -> String              -- Distinguishes one sort of derived name from another
417          -> String
418          -> OccName
419
420 mk_deriv occ_sp sys_prefix str = mkOccName occ_sp (sys_prefix ++ str)
421 \end{code}
422
423 \begin{code}
424 mkDataConWrapperOcc, mkWorkerOcc, mkDefaultMethodOcc, mkDerivedTyConOcc,
425         mkClassTyConOcc, mkClassDataConOcc, mkDictOcc, mkIPOcc, 
426         mkSpecOcc, mkForeignExportOcc, mkGenOcc1, mkGenOcc2,
427         mkDataTOcc, mkDataCOcc, mkDataConWorkerOcc, mkNewTyCoOcc
428    :: OccName -> OccName
429
430 -- These derived variables have a prefix that no Haskell value could have
431 mkDataConWrapperOcc = mk_simple_deriv varName  "$W"
432 mkWorkerOcc         = mk_simple_deriv varName  "$w"
433 mkDefaultMethodOcc  = mk_simple_deriv varName  "$dm"
434 mkDerivedTyConOcc   = mk_simple_deriv tcName   ":"      -- The : prefix makes sure it classifies
435 mkClassTyConOcc     = mk_simple_deriv tcName   ":T"     -- as a tycon/datacon
436 mkClassDataConOcc   = mk_simple_deriv dataName ":D"     -- We go straight to the "real" data con
437                                                         -- for datacons from classes
438 mkDictOcc           = mk_simple_deriv varName  "$d"
439 mkIPOcc             = mk_simple_deriv varName  "$i"
440 mkSpecOcc           = mk_simple_deriv varName  "$s"
441 mkForeignExportOcc  = mk_simple_deriv varName  "$f"
442 mkNewTyCoOcc        = mk_simple_deriv tcName  ":Co"
443 mkInstTyCoOcc       = mk_simple_deriv tcName  ":Co"      -- derived from rep ty
444
445 -- Generic derivable classes
446 mkGenOcc1           = mk_simple_deriv varName  "$gfrom"
447 mkGenOcc2           = mk_simple_deriv varName  "$gto" 
448
449 -- data T = MkT ... deriving( Data ) needs defintions for 
450 --      $tT   :: Data.Generics.Basics.DataType
451 --      $cMkT :: Data.Generics.Basics.Constr
452 mkDataTOcc = mk_simple_deriv varName  "$t"
453 mkDataCOcc = mk_simple_deriv varName  "$c"
454
455 mk_simple_deriv sp px occ = mk_deriv sp px (occNameString occ)
456
457 -- Data constructor workers are made by setting the name space
458 -- of the data constructor OccName (which should be a DataName)
459 -- to VarName
460 mkDataConWorkerOcc datacon_occ = setOccNameSpace varName datacon_occ 
461 \end{code}
462
463 \begin{code}
464 mkSuperDictSelOcc :: Int        -- Index of superclass, eg 3
465                   -> OccName    -- Class, eg "Ord"
466                   -> OccName    -- eg "$p3Ord"
467 mkSuperDictSelOcc index cls_occ
468   = mk_deriv varName "$p" (show index ++ occNameString cls_occ)
469
470 mkLocalOcc :: Unique            -- Unique
471            -> OccName           -- Local name (e.g. "sat")
472            -> OccName           -- Nice unique version ("$L23sat")
473 mkLocalOcc uniq occ
474    = mk_deriv varName ("$L" ++ show uniq) (occNameString occ)
475         -- The Unique might print with characters 
476         -- that need encoding (e.g. 'z'!)
477 \end{code}
478
479 Derive a name for the representation type constructor of a data/newtype
480 instance.
481
482 \begin{code}
483 mkInstTyTcOcc :: Int                    -- Index
484               -> OccName                -- Family name (e.g. "Map")
485               -> OccName                -- Nice unique version (":R23Map")
486 mkInstTyTcOcc index occ
487    = mk_deriv tcName (":R" ++ show index) (occNameString occ)
488 \end{code}
489
490 \begin{code}
491 mkDFunOcc :: String             -- Typically the class and type glommed together e.g. "OrdMaybe"
492                                 -- Only used in debug mode, for extra clarity
493           -> Bool               -- True <=> hs-boot instance dfun
494           -> Int                -- Unique index
495           -> OccName            -- "$f3OrdMaybe"
496
497 -- In hs-boot files we make dict funs like $fx7ClsTy, which get bound to the real
498 -- thing when we compile the mother module. Reason: we don't know exactly
499 -- what the  mother module will call it.
500
501 mkDFunOcc info_str is_boot index 
502   = mk_deriv VarName prefix string
503   where
504     prefix | is_boot   = "$fx"
505            | otherwise = "$f"
506     string | opt_PprStyle_Debug = show index ++ info_str
507            | otherwise          = show index
508 \end{code}
509
510 We used to add a '$m' to indicate a method, but that gives rise to bad
511 error messages from the type checker when we print the function name or pattern
512 of an instance-decl binding.  Why? Because the binding is zapped
513 to use the method name in place of the selector name.
514 (See TcClassDcl.tcMethodBind)
515
516 The way it is now, -ddump-xx output may look confusing, but
517 you can always say -dppr-debug to get the uniques.
518
519 However, we *do* have to zap the first character to be lower case,
520 because overloaded constructors (blarg) generate methods too.
521 And convert to VarName space
522
523 e.g. a call to constructor MkFoo where
524         data (Ord a) => Foo a = MkFoo a
525
526 If this is necessary, we do it by prefixing '$m'.  These 
527 guys never show up in error messages.  What a hack.
528
529 \begin{code}
530 mkMethodOcc :: OccName -> OccName
531 mkMethodOcc occ@(OccName VarName fs) = occ
532 mkMethodOcc occ                      = mk_simple_deriv varName "$m" occ
533 \end{code}
534
535
536 %************************************************************************
537 %*                                                                      *
538 \subsection{Tidying them up}
539 %*                                                                      *
540 %************************************************************************
541
542 Before we print chunks of code we like to rename it so that
543 we don't have to print lots of silly uniques in it.  But we mustn't
544 accidentally introduce name clashes!  So the idea is that we leave the
545 OccName alone unless it accidentally clashes with one that is already
546 in scope; if so, we tack on '1' at the end and try again, then '2', and
547 so on till we find a unique one.
548
549 There's a wrinkle for operators.  Consider '>>='.  We can't use '>>=1' 
550 because that isn't a single lexeme.  So we encode it to 'lle' and *then*
551 tack on the '1', if necessary.
552
553 \begin{code}
554 type TidyOccEnv = OccEnv Int    -- The in-scope OccNames
555         -- Range gives a plausible starting point for new guesses
556
557 emptyTidyOccEnv = emptyOccEnv
558
559 initTidyOccEnv :: [OccName] -> TidyOccEnv       -- Initialise with names to avoid!
560 initTidyOccEnv = foldl (\env occ -> extendOccEnv env occ 1) emptyTidyOccEnv
561
562 tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName)
563
564 tidyOccName in_scope occ@(OccName occ_sp fs)
565   = case lookupOccEnv in_scope occ of
566         Nothing ->      -- Not already used: make it used
567                    (extendOccEnv in_scope occ 1, occ)
568
569         Just n  ->      -- Already used: make a new guess, 
570                         -- change the guess base, and try again
571                    tidyOccName  (extendOccEnv in_scope occ (n+1))
572                                 (mkOccName occ_sp (unpackFS fs ++ show n))
573 \end{code}
574
575 %************************************************************************
576 %*                                                                      *
577                 Stuff for dealing with tuples
578 %*                                                                      *
579 %************************************************************************
580
581 \begin{code}
582 mkTupleOcc :: NameSpace -> Boxity -> Arity -> OccName
583 mkTupleOcc ns bx ar = OccName ns (mkFastString str)
584   where
585         -- no need to cache these, the caching is done in the caller
586         -- (TysWiredIn.mk_tuple)
587     str = case bx of
588                 Boxed   -> '(' : commas ++ ")"
589                 Unboxed -> '(' : '#' : commas ++ "#)"
590
591     commas = take (ar-1) (repeat ',')
592
593 isTupleOcc_maybe :: OccName -> Maybe (NameSpace, Boxity, Arity)
594 -- Tuples are special, because there are so many of them!
595 isTupleOcc_maybe (OccName ns fs)
596   = case unpackFS fs of
597         '(':'#':',':rest -> Just (ns, Unboxed, 2 + count_commas rest)
598         '(':',':rest     -> Just (ns, Boxed,   2 + count_commas rest)
599         _other           -> Nothing
600   where
601     count_commas (',':rest) = 1 + count_commas rest
602     count_commas _          = 0
603 \end{code}
604
605 %************************************************************************
606 %*                                                                      *
607 \subsection{Lexical categories}
608 %*                                                                      *
609 %************************************************************************
610
611 These functions test strings to see if they fit the lexical categories
612 defined in the Haskell report.
613
614 \begin{code}
615 isLexCon,   isLexVar,    isLexId,    isLexSym    :: FastString -> Bool
616 isLexConId, isLexConSym, isLexVarId, isLexVarSym :: FastString -> Bool
617
618 isLexCon cs = isLexConId  cs || isLexConSym cs
619 isLexVar cs = isLexVarId  cs || isLexVarSym cs
620
621 isLexId  cs = isLexConId  cs || isLexVarId  cs
622 isLexSym cs = isLexConSym cs || isLexVarSym cs
623
624 -------------
625
626 isLexConId cs                           -- Prefix type or data constructors
627   | nullFS cs         = False           --      e.g. "Foo", "[]", "(,)" 
628   | cs == FSLIT("[]") = True
629   | otherwise         = startsConId (headFS cs)
630
631 isLexVarId cs                           -- Ordinary prefix identifiers
632   | nullFS cs         = False           --      e.g. "x", "_x"
633   | otherwise         = startsVarId (headFS cs)
634
635 isLexConSym cs                          -- Infix type or data constructors
636   | nullFS cs         = False           --      e.g. ":-:", ":", "->"
637   | cs == FSLIT("->") = True
638   | otherwise         = startsConSym (headFS cs)
639
640 isLexVarSym cs                          -- Infix identifiers
641   | nullFS cs         = False           --      e.g. "+"
642   | otherwise         = startsVarSym (headFS cs)
643
644 -------------
645 startsVarSym, startsVarId, startsConSym, startsConId :: Char -> Bool
646 startsVarSym c = isSymbolASCII c || (ord c > 0x7f && isSymbol c) -- Infix Ids
647 startsConSym c = c == ':'                               -- Infix data constructors
648 startsVarId c  = isLower c || c == '_'  -- Ordinary Ids
649 startsConId c  = isUpper c || c == '('  -- Ordinary type constructors and data constructors
650
651 isSymbolASCII c = c `elem` "!#$%&*+./<=>?@\\^|~-"
652 \end{code}
653
654 %************************************************************************
655 %*                                                                      *
656                 Binary instance
657     Here rather than BinIface because OccName is abstract
658 %*                                                                      *
659 %************************************************************************
660
661 \begin{code}
662 instance Binary NameSpace where
663     put_ bh VarName = do
664             putByte bh 0
665     put_ bh DataName = do
666             putByte bh 1
667     put_ bh TvName = do
668             putByte bh 2
669     put_ bh TcClsName = do
670             putByte bh 3
671     get bh = do
672             h <- getByte bh
673             case h of
674               0 -> do return VarName
675               1 -> do return DataName
676               2 -> do return TvName
677               _ -> do return TcClsName
678
679 instance Binary OccName where
680     put_ bh (OccName aa ab) = do
681             put_ bh aa
682             put_ bh ab
683     get bh = do
684           aa <- get bh
685           ab <- get bh
686           return (OccName aa ab)
687 \end{code}