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