Doc nit in OccName
[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, mkOccEnv_C, 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 mkOccEnv_C   :: (a -> a -> a) -> [(OccName,a)] -> OccEnv a
263 elemOccEnv   :: OccName -> OccEnv a -> Bool
264 foldOccEnv   :: (a -> b -> b) -> b -> OccEnv a -> b
265 occEnvElts   :: OccEnv a -> [a]
266 extendOccEnv_C :: (a->a->a) -> OccEnv a -> OccName -> a -> OccEnv a
267 plusOccEnv     :: OccEnv a -> OccEnv a -> OccEnv a
268 plusOccEnv_C   :: (a->a->a) -> OccEnv a -> OccEnv a -> OccEnv a
269 mapOccEnv      :: (a->b) -> OccEnv a -> OccEnv b
270
271 emptyOccEnv      = emptyUFM
272 unitOccEnv       = unitUFM
273 extendOccEnv     = addToUFM
274 extendOccEnvList = addListToUFM
275 lookupOccEnv     = lookupUFM
276 mkOccEnv         = listToUFM
277 elemOccEnv       = elemUFM
278 foldOccEnv       = foldUFM
279 occEnvElts       = eltsUFM
280 plusOccEnv       = plusUFM
281 plusOccEnv_C     = plusUFM_C
282 extendOccEnv_C   = addToUFM_C
283 mapOccEnv        = mapUFM
284
285 mkOccEnv_C comb l = addListToUFM_C comb emptyOccEnv l
286
287 type OccSet = UniqFM OccName
288
289 emptyOccSet       :: OccSet
290 unitOccSet        :: OccName -> OccSet
291 mkOccSet          :: [OccName] -> OccSet
292 extendOccSet      :: OccSet -> OccName -> OccSet
293 extendOccSetList  :: OccSet -> [OccName] -> OccSet
294 unionOccSets      :: OccSet -> OccSet -> OccSet
295 unionManyOccSets  :: [OccSet] -> OccSet
296 minusOccSet       :: OccSet -> OccSet -> OccSet
297 elemOccSet        :: OccName -> OccSet -> Bool
298 occSetElts        :: OccSet -> [OccName]
299 foldOccSet        :: (OccName -> b -> b) -> b -> OccSet -> b
300 isEmptyOccSet     :: OccSet -> Bool
301 intersectOccSet   :: OccSet -> OccSet -> OccSet
302 intersectsOccSet  :: OccSet -> OccSet -> Bool
303
304 emptyOccSet       = emptyUniqSet
305 unitOccSet        = unitUniqSet
306 mkOccSet          = mkUniqSet
307 extendOccSet      = addOneToUniqSet
308 extendOccSetList  = addListToUniqSet
309 unionOccSets      = unionUniqSets
310 unionManyOccSets  = unionManyUniqSets
311 minusOccSet       = minusUniqSet
312 elemOccSet        = elementOfUniqSet
313 occSetElts        = uniqSetToList
314 foldOccSet        = foldUniqSet
315 isEmptyOccSet     = isEmptyUniqSet
316 intersectOccSet   = intersectUniqSets
317 intersectsOccSet s1 s2 = not (isEmptyOccSet (s1 `intersectOccSet` s2))
318 \end{code}
319
320
321 %************************************************************************
322 %*                                                                      *
323 \subsection{Predicates and taking them apart}
324 %*                                                                      *
325 %************************************************************************
326
327 \begin{code}
328 occNameString :: OccName -> String
329 occNameString (OccName _ s) = unpackFS s
330
331 setOccNameSpace :: NameSpace -> OccName -> OccName
332 setOccNameSpace sp (OccName _ occ) = OccName sp occ
333
334 isVarOcc, isTvOcc, isDataSymOcc, isSymOcc, isTcOcc :: OccName -> Bool
335
336 isVarOcc (OccName VarName _) = True
337 isVarOcc other               = False
338
339 isTvOcc (OccName TvName _) = True
340 isTvOcc other              = False
341
342 isTcOcc (OccName TcClsName _) = True
343 isTcOcc other                 = False
344
345 isValOcc (OccName VarName  _) = True
346 isValOcc (OccName DataName _) = True
347 isValOcc other                = False
348
349 -- Data constructor operator (starts with ':', or '[]')
350 -- Pretty inefficient!
351 isDataSymOcc (OccName DataName s) = isLexConSym s
352 isDataSymOcc (OccName VarName s)  
353   | isLexConSym s = pprPanic "isDataSymOcc: check me" (ppr s)
354                 -- Jan06: I don't think this should happen
355 isDataSymOcc other                = False
356
357 isDataOcc (OccName DataName _) = True
358 isDataOcc (OccName VarName s)  
359   | isLexCon s = pprPanic "isDataOcc: check me" (ppr s)
360                 -- Jan06: I don't think this should happen
361 isDataOcc other                = False
362
363 -- Any operator (data constructor or variable)
364 -- Pretty inefficient!
365 isSymOcc (OccName DataName s)  = isLexConSym s
366 isSymOcc (OccName TcClsName s) = isLexConSym s
367 isSymOcc (OccName VarName s)   = isLexSym s
368 isSymOcc other                 = False
369
370 parenSymOcc :: OccName -> SDoc -> SDoc
371 -- Wrap parens around an operator
372 parenSymOcc occ doc | isSymOcc occ = parens doc
373                     | otherwise    = doc
374 \end{code}
375
376
377 \begin{code}
378 reportIfUnused :: OccName -> Bool
379   -- Haskell 98 encourages compilers to suppress warnings about
380   -- unused names in a pattern if they start with "_".
381 reportIfUnused occ = case occNameString occ of
382                         ('_' : _) -> False
383                         _other    -> True
384 \end{code}
385
386
387 %************************************************************************
388 %*                                                                      *
389 \subsection{Making system names}
390 %*                                                                      *
391 %************************************************************************
392
393 Here's our convention for splitting up the interface file name space:
394
395         d...            dictionary identifiers
396                         (local variables, so no name-clash worries)
397
398         $f...           dict-fun identifiers (from inst decls)
399         $dm...          default methods
400         $p...           superclass selectors
401         $w...           workers
402         :T...           compiler-generated tycons for dictionaries
403         :D...           ...ditto data cons
404         :Co...          ...ditto coercions
405         $sf..           specialised version of f
406
407         in encoded form these appear as Zdfxxx etc
408
409         :...            keywords (export:, letrec: etc.)
410 --- I THINK THIS IS WRONG!
411
412 This knowledge is encoded in the following functions.
413
414
415 @mk_deriv@ generates an @OccName@ from the prefix and a string.
416 NB: The string must already be encoded!
417
418 \begin{code}
419 mk_deriv :: NameSpace 
420          -> String              -- Distinguishes one sort of derived name from another
421          -> String
422          -> OccName
423
424 mk_deriv occ_sp sys_prefix str = mkOccName occ_sp (sys_prefix ++ str)
425 \end{code}
426
427 \begin{code}
428 mkDataConWrapperOcc, mkWorkerOcc, mkDefaultMethodOcc, mkDerivedTyConOcc,
429         mkClassTyConOcc, mkClassDataConOcc, mkDictOcc, mkIPOcc, 
430         mkSpecOcc, mkForeignExportOcc, mkGenOcc1, mkGenOcc2,
431         mkDataTOcc, mkDataCOcc, mkDataConWorkerOcc, mkNewTyCoOcc
432    :: OccName -> OccName
433
434 -- These derived variables have a prefix that no Haskell value could have
435 mkDataConWrapperOcc = mk_simple_deriv varName  "$W"
436 mkWorkerOcc         = mk_simple_deriv varName  "$w"
437 mkDefaultMethodOcc  = mk_simple_deriv varName  "$dm"
438 mkDerivedTyConOcc   = mk_simple_deriv tcName   ":"      -- The : prefix makes sure it classifies
439 mkClassTyConOcc     = mk_simple_deriv tcName   ":T"     -- as a tycon/datacon
440 mkClassDataConOcc   = mk_simple_deriv dataName ":D"     -- We go straight to the "real" data con
441                                                         -- for datacons from classes
442 mkDictOcc           = mk_simple_deriv varName  "$d"
443 mkIPOcc             = mk_simple_deriv varName  "$i"
444 mkSpecOcc           = mk_simple_deriv varName  "$s"
445 mkForeignExportOcc  = mk_simple_deriv varName  "$f"
446 mkNewTyCoOcc        = mk_simple_deriv tcName  ":Co"
447 mkInstTyCoOcc       = mk_simple_deriv tcName  ":Co"      -- derived from rep ty
448
449 -- Generic derivable classes
450 mkGenOcc1           = mk_simple_deriv varName  "$gfrom"
451 mkGenOcc2           = mk_simple_deriv varName  "$gto" 
452
453 -- data T = MkT ... deriving( Data ) needs defintions for 
454 --      $tT   :: Data.Generics.Basics.DataType
455 --      $cMkT :: Data.Generics.Basics.Constr
456 mkDataTOcc = mk_simple_deriv varName  "$t"
457 mkDataCOcc = mk_simple_deriv varName  "$c"
458
459 mk_simple_deriv sp px occ = mk_deriv sp px (occNameString occ)
460
461 -- Data constructor workers are made by setting the name space
462 -- of the data constructor OccName (which should be a DataName)
463 -- to VarName
464 mkDataConWorkerOcc datacon_occ = setOccNameSpace varName datacon_occ 
465 \end{code}
466
467 \begin{code}
468 mkSuperDictSelOcc :: Int        -- Index of superclass, eg 3
469                   -> OccName    -- Class, eg "Ord"
470                   -> OccName    -- eg "$p3Ord"
471 mkSuperDictSelOcc index cls_occ
472   = mk_deriv varName "$p" (show index ++ occNameString cls_occ)
473
474 mkLocalOcc :: Unique            -- Unique
475            -> OccName           -- Local name (e.g. "sat")
476            -> OccName           -- Nice unique version ("$L23sat")
477 mkLocalOcc uniq occ
478    = mk_deriv varName ("$L" ++ show uniq) (occNameString occ)
479         -- The Unique might print with characters 
480         -- that need encoding (e.g. 'z'!)
481 \end{code}
482
483 Derive a name for the representation type constructor of a data/newtype
484 instance.
485
486 \begin{code}
487 mkInstTyTcOcc :: Int                    -- Index
488               -> OccName                -- Family name (e.g. "Map")
489               -> OccName                -- Nice unique version (":R23Map")
490 mkInstTyTcOcc index occ
491    = mk_deriv tcName (":R" ++ show index) (occNameString occ)
492 \end{code}
493
494 \begin{code}
495 mkDFunOcc :: String             -- Typically the class and type glommed together e.g. "OrdMaybe"
496                                 -- Only used in debug mode, for extra clarity
497           -> Bool               -- True <=> hs-boot instance dfun
498           -> Int                -- Unique index
499           -> OccName            -- "$f3OrdMaybe"
500
501 -- In hs-boot files we make dict funs like $fx7ClsTy, which get bound to the real
502 -- thing when we compile the mother module. Reason: we don't know exactly
503 -- what the  mother module will call it.
504
505 mkDFunOcc info_str is_boot index 
506   = mk_deriv VarName prefix string
507   where
508     prefix | is_boot   = "$fx"
509            | otherwise = "$f"
510     string | opt_PprStyle_Debug = show index ++ info_str
511            | otherwise          = show index
512 \end{code}
513
514 We used to add a '$m' to indicate a method, but that gives rise to bad
515 error messages from the type checker when we print the function name or pattern
516 of an instance-decl binding.  Why? Because the binding is zapped
517 to use the method name in place of the selector name.
518 (See TcClassDcl.tcMethodBind)
519
520 The way it is now, -ddump-xx output may look confusing, but
521 you can always say -dppr-debug to get the uniques.
522
523 However, we *do* have to zap the first character to be lower case,
524 because overloaded constructors (blarg) generate methods too.
525 And convert to VarName space
526
527 e.g. a call to constructor MkFoo where
528         data (Ord a) => Foo a = MkFoo a
529
530 If this is necessary, we do it by prefixing '$m'.  These 
531 guys never show up in error messages.  What a hack.
532
533 \begin{code}
534 mkMethodOcc :: OccName -> OccName
535 mkMethodOcc occ@(OccName VarName fs) = occ
536 mkMethodOcc occ                      = mk_simple_deriv varName "$m" occ
537 \end{code}
538
539
540 %************************************************************************
541 %*                                                                      *
542 \subsection{Tidying them up}
543 %*                                                                      *
544 %************************************************************************
545
546 Before we print chunks of code we like to rename it so that
547 we don't have to print lots of silly uniques in it.  But we mustn't
548 accidentally introduce name clashes!  So the idea is that we leave the
549 OccName alone unless it accidentally clashes with one that is already
550 in scope; if so, we tack on '1' at the end and try again, then '2', and
551 so on till we find a unique one.
552
553 There's a wrinkle for operators.  Consider '>>='.  We can't use '>>=1' 
554 because that isn't a single lexeme.  So we encode it to 'lle' and *then*
555 tack on the '1', if necessary.
556
557 \begin{code}
558 type TidyOccEnv = OccEnv Int    -- The in-scope OccNames
559         -- Range gives a plausible starting point for new guesses
560
561 emptyTidyOccEnv = emptyOccEnv
562
563 initTidyOccEnv :: [OccName] -> TidyOccEnv       -- Initialise with names to avoid!
564 initTidyOccEnv = foldl (\env occ -> extendOccEnv env occ 1) emptyTidyOccEnv
565
566 tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName)
567
568 tidyOccName in_scope occ@(OccName occ_sp fs)
569   = case lookupOccEnv in_scope occ of
570         Nothing ->      -- Not already used: make it used
571                    (extendOccEnv in_scope occ 1, occ)
572
573         Just n  ->      -- Already used: make a new guess, 
574                         -- change the guess base, and try again
575                    tidyOccName  (extendOccEnv in_scope occ (n+1))
576                                 (mkOccName occ_sp (unpackFS fs ++ show n))
577 \end{code}
578
579 %************************************************************************
580 %*                                                                      *
581                 Stuff for dealing with tuples
582 %*                                                                      *
583 %************************************************************************
584
585 \begin{code}
586 mkTupleOcc :: NameSpace -> Boxity -> Arity -> OccName
587 mkTupleOcc ns bx ar = OccName ns (mkFastString str)
588   where
589         -- no need to cache these, the caching is done in the caller
590         -- (TysWiredIn.mk_tuple)
591     str = case bx of
592                 Boxed   -> '(' : commas ++ ")"
593                 Unboxed -> '(' : '#' : commas ++ "#)"
594
595     commas = take (ar-1) (repeat ',')
596
597 isTupleOcc_maybe :: OccName -> Maybe (NameSpace, Boxity, Arity)
598 -- Tuples are special, because there are so many of them!
599 isTupleOcc_maybe (OccName ns fs)
600   = case unpackFS fs of
601         '(':'#':',':rest -> Just (ns, Unboxed, 2 + count_commas rest)
602         '(':',':rest     -> Just (ns, Boxed,   2 + count_commas rest)
603         _other           -> Nothing
604   where
605     count_commas (',':rest) = 1 + count_commas rest
606     count_commas _          = 0
607 \end{code}
608
609 %************************************************************************
610 %*                                                                      *
611 \subsection{Lexical categories}
612 %*                                                                      *
613 %************************************************************************
614
615 These functions test strings to see if they fit the lexical categories
616 defined in the Haskell report.
617
618 \begin{code}
619 isLexCon,   isLexVar,    isLexId,    isLexSym    :: FastString -> Bool
620 isLexConId, isLexConSym, isLexVarId, isLexVarSym :: FastString -> Bool
621
622 isLexCon cs = isLexConId  cs || isLexConSym cs
623 isLexVar cs = isLexVarId  cs || isLexVarSym cs
624
625 isLexId  cs = isLexConId  cs || isLexVarId  cs
626 isLexSym cs = isLexConSym cs || isLexVarSym cs
627
628 -------------
629
630 isLexConId cs                           -- Prefix type or data constructors
631   | nullFS cs         = False           --      e.g. "Foo", "[]", "(,)" 
632   | cs == FSLIT("[]") = True
633   | otherwise         = startsConId (headFS cs)
634
635 isLexVarId cs                           -- Ordinary prefix identifiers
636   | nullFS cs         = False           --      e.g. "x", "_x"
637   | otherwise         = startsVarId (headFS cs)
638
639 isLexConSym cs                          -- Infix type or data constructors
640   | nullFS cs         = False           --      e.g. ":-:", ":", "->"
641   | cs == FSLIT("->") = True
642   | otherwise         = startsConSym (headFS cs)
643
644 isLexVarSym cs                          -- Infix identifiers
645   | nullFS cs         = False           --      e.g. "+"
646   | otherwise         = startsVarSym (headFS cs)
647
648 -------------
649 startsVarSym, startsVarId, startsConSym, startsConId :: Char -> Bool
650 startsVarSym c = isSymbolASCII c || (ord c > 0x7f && isSymbol c) -- Infix Ids
651 startsConSym c = c == ':'                               -- Infix data constructors
652 startsVarId c  = isLower c || c == '_'  -- Ordinary Ids
653 startsConId c  = isUpper c || c == '('  -- Ordinary type constructors and data constructors
654
655 isSymbolASCII c = c `elem` "!#$%&*+./<=>?@\\^|~-"
656 \end{code}
657
658 %************************************************************************
659 %*                                                                      *
660                 Binary instance
661     Here rather than BinIface because OccName is abstract
662 %*                                                                      *
663 %************************************************************************
664
665 \begin{code}
666 instance Binary NameSpace where
667     put_ bh VarName = do
668             putByte bh 0
669     put_ bh DataName = do
670             putByte bh 1
671     put_ bh TvName = do
672             putByte bh 2
673     put_ bh TcClsName = do
674             putByte bh 3
675     get bh = do
676             h <- getByte bh
677             case h of
678               0 -> do return VarName
679               1 -> do return DataName
680               2 -> do return TvName
681               _ -> do return TcClsName
682
683 instance Binary OccName where
684     put_ bh (OccName aa ab) = do
685             put_ bh aa
686             put_ bh ab
687     get bh = do
688           aa <- get bh
689           ab <- get bh
690           return (OccName aa ab)
691 \end{code}