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