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