[project @ 1996-01-08 20:28:12 by partain]
[ghc-hetmet.git] / ghc / compiler / basicTypes / NameTypes.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1994
3 %
4 %************************************************************************
5 %*                                                                      *
6 \section[NameTypes]{@NameTypes@: The flavours of names that we stick on things}
7 %*                                                                      *
8 %************************************************************************
9
10 \begin{code}
11 #include "HsVersions.h"
12
13 module NameTypes (
14         ShortName, FullName,    -- abstract types
15         Provenance(..),
16
17         fromPrelude,
18
19         mkShortName,
20
21         mkFullName, mkPrivateFullName, mkPreludeCoreName,
22
23         invisibleFullName,
24
25         unlocaliseFullName, unlocaliseShortName,
26
27 #ifdef DPH
28         isInventedFullName,
29 #endif {- Data Parallel Haskell -}
30
31         -- and to make the interface self-sufficient....
32         ExportFlag, Unique, SrcLoc
33     ) where
34
35 import CLabelInfo       ( identToC, cSEP )
36 import Outputable
37 import PrelFuns         ( pRELUDE, pRELUDE_CORE ) -- NB: naughty import
38 import Pretty
39 import SrcLoc           ( SrcLoc, mkBuiltinSrcLoc )
40 import Unique           ( showUnique, Unique )
41 import Util
42 \end{code}
43
44 %************************************************************************
45 %*                                                                      *
46 \subsection[NameTypes-flavours]{Datatypes for names}
47 %*                                                                      *
48 %************************************************************************
49
50 Here are the types; see the notes that follow.
51 \begin{code}
52 data ShortName
53   = ShortName       FAST_STRING -- entity's name in this module
54                     SrcLoc      -- defining location (only one possible)
55
56 data FullName
57   = FullName        FAST_STRING -- original module name
58                     FAST_STRING -- entity's name in original module
59                     Provenance  -- where this thing came from
60                                 -- (also records its local name, if any)
61                     ExportFlag  -- where this thing is going (from here)
62                     Bool        -- True <=> invisible to the user
63                     SrcLoc      -- defining location (just one)
64 \end{code}
65 (@FullNames@ don't have fast-comparison keys; the things with
66 @FullNames@ do.)
67
68 \begin{description}
69 %----------------------------------------------------------------------
70 \item[@ShortName@:]
71
72 These are used for entities local to the module being compiled; for
73 example, function parameters, where- and let-bound things.  These are
74 @TyVars@ (ToDo: what if imported???) and local @Ids@.  They have
75 @Uniques@ for fast comparison.
76
77 %----------------------------------------------------------------------
78 \item[@FullName@:]
79 These are used for things that either have, or may be required to
80 have, full-blown original names.  All @Classes@ and @TyCons@ have full
81 names.  All data-constructor and top-level @Ids@ (things that were
82 top-level in the original source) have fullnames.
83 \end{description}
84
85 %************************************************************************
86 %*                                                                      *
87 \subsection[NameTypes-Provenance]{Where a name(d thing) came from}
88 %*                                                                      *
89 %************************************************************************
90
91 The ``provenance'' of a name says something about where it came from.
92 This is used:
93 \begin{itemize}
94 \item
95 to decide whether to generate the code fragments for constructors
96 (only done for @ThisModule@).
97 \item
98 to detect when a thing is from @PreludeCore@, in which case we
99 use shorter target-code names.
100 \end{itemize}
101
102 \begin{code}
103 data Provenance
104   = ThisModule
105
106   | InventedInThisModule        -- for workers/wrappers, specialized
107                                 -- versions, etc: anything "conjured up"
108                                 -- on the compiler's initiative.
109
110   | ExportedByPreludeCore       -- these are the immutable, unrenamable
111                                 -- things the compiler knows about
112
113   | OtherPrelude    FAST_STRING -- the FullName gave the *original*
114                                 -- name; this says what it was renamed
115                                 -- to (if anything); really just for
116                                 -- pretty-printing
117
118   | OtherModule     FAST_STRING -- as for OtherPrelude, just the occurrence
119                                 -- name
120                     [FAST_STRING]-- The modules from whose interface we
121                                 -- got the information about this thing
122
123   | HereInPreludeCore           -- used when compiling PreludeCore bits:
124                                 -- == ThisModule + ExportedByPreludeCore
125
126   | OtherInstance               -- For imported instances.
127                     FAST_STRING -- The module where this instance supposedly
128                                 -- was declared; "" if we don't know.
129                     [FAST_STRING] -- The modules whose interface told us about
130                                 -- this instance.
131 \end{code}
132
133 %************************************************************************
134 %*                                                                      *
135 \subsection[NameTypes-access-fns]{Access functions for names}
136 %*                                                                      *
137 %************************************************************************
138
139 Things to make 'em:
140 \begin{code}
141 mkShortName = ShortName
142
143 mkFullName m n p e l = FullName m n p e False{-not invisible-} l
144
145 mkPrivateFullName m n p e l = FullName m n p e True{-invisible-} l
146
147 mkPreludeCoreName mod name
148   = FullName mod name ExportedByPreludeCore ExportAll False mkBuiltinSrcLoc
149     -- Mark them as Exported; mkInterface may decide against it
150     -- later.  (Easier than marking them NotExported, then later
151     -- deciding it would be a good idea...)
152 \end{code}
153
154 \begin{code}
155 #ifdef DPH
156 isInventedFullName (FullName _ _ p _ _ _)
157   = case p of
158       InventedInThisModule -> True
159       _                    -> False
160
161 #endif {- Data Parallel Haskell -}
162 \end{code}
163
164 \begin{code}
165 unlocaliseShortName :: FAST_STRING -> Unique -> ShortName -> FullName
166
167 {- We now elucidate Simon's favourite piece of code:
168
169    When we are told to "unlocalise" a ShortName, we really really want
170    the resulting monster to be unique (across the entire universe).
171    We can't count on the module name being printed (for Prelude
172    things, it isn't), so we brutally force the module-name into the
173    regular-name component.
174
175    We change the provenance to InventedInThisModule, because
176    that's what it is.
177 -}
178 unlocaliseShortName mod u (ShortName nm loc)
179   = FullName mod
180             (mod _APPEND_ nm _APPEND_ (showUnique u))
181             InventedInThisModule
182             ExportAll False loc
183
184 -- FullNames really can't be mangled; someone out there
185 -- *expects* the thing to have this name.
186 -- We only change the export status.
187
188 unlocaliseFullName (FullName m n p _ i l)
189   = FullName m n p ExportAll i l
190 \end{code}
191
192 %************************************************************************
193 %*                                                                      *
194 \subsection[NameTypes-instances]{Instance declarations for various names}
195 %*                                                                      *
196 %************************************************************************
197
198 We don't have equality and ordering; that's defined for the things
199 that have @ShortNames@ and @FullNames@ in them.
200
201 \begin{code}
202 instance NamedThing ShortName where
203     getExportFlag a                   = NotExported
204     isLocallyDefined a                = True
205     getOrigName (ShortName s l)       = (panic "NamedThing.ShortName.getOrigName", s)
206     getOccurrenceName (ShortName s l) = s
207     getSrcLoc   (ShortName s l)       = l
208     fromPreludeCore (ShortName _ _)   = False
209 #ifdef DEBUG
210     getTheUnique (ShortName s l)      = panic "NamedThing.ShortName.getTheUnique" 
211     getInformingModules a             = panic "NamedThing.ShortName.getInformingModule"
212     hasType a                         = panic "NamedThing.ShortName.hasType"
213     getType a                         = panic "NamedThing.ShortName.getType"
214 #endif
215 \end{code}
216
217 \begin{code}
218 instance NamedThing FullName where
219
220     getExportFlag     (FullName m s p e i l) = e
221     getOrigName       (FullName m s p e i l) = (m, s)
222     getSrcLoc         (FullName m s p e i l) = l
223
224     isLocallyDefined  (FullName m s p e i l)
225       = case p of
226           ThisModule           -> True
227           InventedInThisModule -> True
228           HereInPreludeCore    -> True
229           _                    -> False
230
231     getOccurrenceName (FullName _ s p _ _ _)
232       = case p of
233           OtherPrelude o   -> o
234           OtherModule  o _ -> o
235           _                -> s
236
237     fromPreludeCore (FullName _ _ p _ _ _)
238       = case p of
239           ExportedByPreludeCore -> True
240           HereInPreludeCore     -> True
241           _                     -> False
242
243     getInformingModules (FullName _ _ p _ _ _)
244       = case p of
245           ThisModule            -> []   -- Urgh.  ToDo
246           InventedInThisModule  -> []
247           OtherModule   _ ms    -> ms
248           OtherInstance _ ms    -> ms
249           ExportedByPreludeCore -> [pRELUDE_CORE]
250           HereInPreludeCore     -> [pRELUDE_CORE]
251           OtherPrelude _        -> [pRELUDE]
252
253 #ifdef DEBUG
254     getTheUnique = panic "NamedThing.FullName.getTheUnique"
255     hasType = panic "NamedThing.FullName.hasType"
256     getType = panic "NamedThing.FullName.getType"
257 #endif
258 \end{code}
259
260 A hack (ToDo?):
261 \begin{code}
262 fromPrelude :: FAST_STRING -> Bool
263
264 fromPrelude s = (_SUBSTR_ s 0 6 == SLIT("Prelude"))
265
266 invisibleFullName (FullName m s p e i l) = i
267 \end{code}
268
269 Forcing and printing:
270 \begin{code}
271 instance Outputable ShortName where
272     ppr sty (ShortName s loc) = ppPStr s
273
274 instance Outputable FullName where
275     ppr sty name@(FullName m s p e i l)
276       = let pp_name =
277               ppBeside (if fromPreludeCore name
278                         then ppNil
279                         else case sty of
280                               PprForUser     -> ppNil
281                               PprDebug       -> ppNil
282                               PprInterface _ -> ppNil
283                               PprUnfolding _ -> ppNil   -- ToDo: something diff later?
284                               PprForC _ -> ppBeside (identToC m) (ppPStr cSEP)
285                               PprForAsm _ False _ -> ppBeside (identToC m) (ppPStr cSEP)
286                               PprForAsm _ True _ -> ppBesides [ppPStr cSEP, identToC m, ppPStr cSEP]
287                               _         -> ppBeside (ppPStr m) (ppChar '.'))
288                        (if codeStyle sty
289                         then identToC s
290                         else case sty of
291                                PprInterface _ -> pp_local_name s p
292                                PprForUser     -> pp_local_name s p
293                                _              -> ppPStr s)
294
295             pp_debug = ppBeside pp_name (pp_occur_name s p)
296         in
297         case sty of
298           PprShowAll     -> ppBesides [pp_debug, pp_exp e] -- (ppr sty loc)
299           PprDebug       -> pp_debug
300           PprUnfolding _ -> pp_debug
301           _              -> pp_name
302       where
303         pp_exp NotExported = ppNil
304         pp_exp ExportAll   = ppPStr SLIT("/EXP(..)")
305         pp_exp ExportAbs   = ppPStr SLIT("/EXP")
306
307 -- little utility gizmos...
308 pp_occur_name, pp_local_name :: FAST_STRING -> Provenance -> Pretty
309
310 pp_occur_name s (OtherPrelude o)  | s /= o = ppBesides [ppChar '{', ppPStr o, ppChar '}']
311 pp_occur_name s (OtherModule o ms)| s /= o = ppBesides [ppChar '{', ppPStr o, ppChar '}']
312         -- ToDo: print the "informant modules"?
313 pp_occur_name _ _                          = ppNil
314
315 pp_local_name s (OtherPrelude o)  | s /= o = ppPStr o
316 pp_local_name s (OtherModule o ms)| s /= o = ppPStr o
317 pp_local_name s _                          = ppPStr s
318 \end{code}