syb no longer needs to be wired in
[ghc-hetmet.git] / compiler / basicTypes / Module.lhs
1 %
2 % (c) The University of Glasgow, 2004-2006
3 %
4
5 Module
6 ~~~~~~~~~~
7 Simply the name of a module, represented as a FastString.
8 These are Uniquable, hence we can build FiniteMaps with Modules as
9 the keys.
10
11 \begin{code}
12 module Module 
13     (
14         -- * The ModuleName type
15         ModuleName,
16         pprModuleName,
17         moduleNameFS,
18         moduleNameString,
19         moduleNameSlashes,
20         mkModuleName,
21         mkModuleNameFS,
22         stableModuleNameCmp,
23
24         -- * The PackageId type
25         PackageId,
26         fsToPackageId,
27         packageIdFS,
28         stringToPackageId,
29         packageIdString,
30         stablePackageIdCmp,
31
32         -- * Wired-in PackageIds
33         -- $wired_in_packages
34         primPackageId,
35         integerPackageId,
36         basePackageId,
37         rtsPackageId,
38         haskell98PackageId,
39         thPackageId,
40         dphSeqPackageId,
41         dphParPackageId,
42         mainPackageId,
43
44         -- * The Module type
45         Module,
46         modulePackageId, moduleName,
47         pprModule,
48         mkModule,
49         stableModuleCmp,
50
51         -- * The ModuleLocation type
52         ModLocation(..),
53         addBootSuffix, addBootSuffix_maybe, addBootSuffixLocn,
54
55         -- * Module mappings
56         ModuleEnv,
57         elemModuleEnv, extendModuleEnv, extendModuleEnvList, 
58         extendModuleEnvList_C, plusModuleEnv_C,
59         delModuleEnvList, delModuleEnv, plusModuleEnv, lookupModuleEnv,
60         lookupWithDefaultModuleEnv, mapModuleEnv, mkModuleEnv, emptyModuleEnv,
61         moduleEnvKeys, moduleEnvElts, unitModuleEnv, isEmptyModuleEnv,
62         foldModuleEnv, extendModuleEnv_C, filterModuleEnv,
63
64         -- * ModuleName mappings
65         ModuleNameEnv,
66
67         -- * Sets of Modules
68         ModuleSet, 
69         emptyModuleSet, mkModuleSet, moduleSetElts, extendModuleSet, elemModuleSet
70     ) where
71
72 import Outputable
73 import qualified Pretty
74 import Unique
75 import FiniteMap
76 import LazyUniqFM
77 import FastString
78 import Binary
79 import Util
80
81 import System.FilePath
82 \end{code}
83
84 %************************************************************************
85 %*                                                                      *
86 \subsection{Module locations}
87 %*                                                                      *
88 %************************************************************************
89
90 \begin{code}
91 -- | Where a module lives on the file system: the actual locations
92 -- of the .hs, .hi and .o files, if we have them
93 data ModLocation
94    = ModLocation {
95         ml_hs_file   :: Maybe FilePath,
96                 -- The source file, if we have one.  Package modules
97                 -- probably don't have source files.
98
99         ml_hi_file   :: FilePath,
100                 -- Where the .hi file is, whether or not it exists
101                 -- yet.  Always of form foo.hi, even if there is an
102                 -- hi-boot file (we add the -boot suffix later)
103
104         ml_obj_file  :: FilePath
105                 -- Where the .o file is, whether or not it exists yet.
106                 -- (might not exist either because the module hasn't
107                 -- been compiled yet, or because it is part of a
108                 -- package with a .a file)
109   } deriving Show
110
111 instance Outputable ModLocation where
112    ppr = text . show
113 \end{code}
114
115 For a module in another package, the hs_file and obj_file
116 components of ModLocation are undefined.  
117
118 The locations specified by a ModLocation may or may not
119 correspond to actual files yet: for example, even if the object
120 file doesn't exist, the ModLocation still contains the path to
121 where the object file will reside if/when it is created.
122
123 \begin{code}
124 addBootSuffix :: FilePath -> FilePath
125 -- ^ Add the @-boot@ suffix to .hs, .hi and .o files
126 addBootSuffix path = path ++ "-boot"
127
128 addBootSuffix_maybe :: Bool -> FilePath -> FilePath
129 -- ^ Add the @-boot@ suffix if the @Bool@ argument is @True@
130 addBootSuffix_maybe is_boot path
131  | is_boot   = addBootSuffix path
132  | otherwise = path
133
134 addBootSuffixLocn :: ModLocation -> ModLocation
135 -- ^ Add the @-boot@ suffix to all file paths associated with the module
136 addBootSuffixLocn locn
137   = locn { ml_hs_file  = fmap addBootSuffix (ml_hs_file locn)
138          , ml_hi_file  = addBootSuffix (ml_hi_file locn)
139          , ml_obj_file = addBootSuffix (ml_obj_file locn) }
140 \end{code}
141
142
143 %************************************************************************
144 %*                                                                      *
145 \subsection{The name of a module}
146 %*                                                                      *
147 %************************************************************************
148
149 \begin{code}
150 -- | A ModuleName is essentially a simple string, e.g. @Data.List@.
151 newtype ModuleName = ModuleName FastString
152
153 instance Uniquable ModuleName where
154   getUnique (ModuleName nm) = getUnique nm
155
156 instance Eq ModuleName where
157   nm1 == nm2 = getUnique nm1 == getUnique nm2
158
159 -- Warning: gives an ordering relation based on the uniques of the
160 -- FastStrings which are the (encoded) module names.  This is _not_
161 -- a lexicographical ordering.
162 instance Ord ModuleName where
163   nm1 `compare` nm2 = getUnique nm1 `compare` getUnique nm2
164
165 instance Outputable ModuleName where
166   ppr = pprModuleName
167
168 instance Binary ModuleName where
169   put_ bh (ModuleName fs) = put_ bh fs
170   get bh = do fs <- get bh; return (ModuleName fs)
171
172 stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering
173 -- ^ Compares module names lexically, rather than by their 'Unique's
174 stableModuleNameCmp n1 n2 = moduleNameFS n1 `compare` moduleNameFS n2
175
176 pprModuleName :: ModuleName -> SDoc
177 pprModuleName (ModuleName nm) = 
178     getPprStyle $ \ sty ->
179     if codeStyle sty 
180         then ftext (zEncodeFS nm)
181         else ftext nm
182
183 moduleNameFS :: ModuleName -> FastString
184 moduleNameFS (ModuleName mod) = mod
185
186 moduleNameString :: ModuleName -> String
187 moduleNameString (ModuleName mod) = unpackFS mod
188
189 mkModuleName :: String -> ModuleName
190 mkModuleName s = ModuleName (mkFastString s)
191
192 mkModuleNameFS :: FastString -> ModuleName
193 mkModuleNameFS s = ModuleName s
194
195 -- | Returns the string version of the module name, with dots replaced by slashes
196 moduleNameSlashes :: ModuleName -> String
197 moduleNameSlashes = dots_to_slashes . moduleNameString
198   where dots_to_slashes = map (\c -> if c == '.' then pathSeparator else c)
199 \end{code}
200
201 %************************************************************************
202 %*                                                                      *
203 \subsection{A fully qualified module}
204 %*                                                                      *
205 %************************************************************************
206
207 \begin{code}
208 -- | A Module is a pair of a 'PackageId' and a 'ModuleName'.
209 data Module = Module {
210    modulePackageId :: !PackageId,  -- pkg-1.0
211    moduleName      :: !ModuleName  -- A.B.C
212   }
213   deriving (Eq, Ord)
214
215 instance Uniquable Module where
216   getUnique (Module p n) = getUnique (packageIdFS p `appendFS` moduleNameFS n)
217
218 instance Outputable Module where
219   ppr = pprModule
220
221 instance Binary Module where
222   put_ bh (Module p n) = put_ bh p >> put_ bh n
223   get bh = do p <- get bh; n <- get bh; return (Module p n)
224
225 -- | This gives a stable ordering, as opposed to the Ord instance which
226 -- gives an ordering based on the 'Unique's of the components, which may
227 -- not be stable from run to run of the compiler.
228 stableModuleCmp :: Module -> Module -> Ordering
229 stableModuleCmp (Module p1 n1) (Module p2 n2) 
230    = (p1 `stablePackageIdCmp`  p2) `thenCmp`
231      (n1 `stableModuleNameCmp` n2)
232
233 mkModule :: PackageId -> ModuleName -> Module
234 mkModule = Module
235
236 pprModule :: Module -> SDoc
237 pprModule mod@(Module p n)  = pprPackagePrefix p mod <> pprModuleName n
238
239 pprPackagePrefix :: PackageId -> Module -> PprStyle -> Pretty.Doc
240 pprPackagePrefix p mod = getPprStyle doc
241  where
242    doc sty
243        | codeStyle sty = 
244           if p == mainPackageId 
245                 then empty -- never qualify the main package in code
246                 else ftext (zEncodeFS (packageIdFS p)) <> char '_'
247        | qualModule sty mod = ftext (packageIdFS (modulePackageId mod)) <> char ':'
248                 -- the PrintUnqualified tells us which modules have to
249                 -- be qualified with package names
250        | otherwise = empty
251 \end{code}
252
253 %************************************************************************
254 %*                                                                      *
255 \subsection{PackageId}
256 %*                                                                      *
257 %************************************************************************
258
259 \begin{code}
260 -- | Essentially just a string identifying a package, including the version: e.g. parsec-1.0
261 newtype PackageId = PId FastString deriving( Eq )
262     -- here to avoid module loops with PackageConfig
263
264 instance Uniquable PackageId where
265  getUnique pid = getUnique (packageIdFS pid)
266
267 -- Note: *not* a stable lexicographic ordering, a faster unique-based
268 -- ordering.
269 instance Ord PackageId where
270   nm1 `compare` nm2 = getUnique nm1 `compare` getUnique nm2
271
272 stablePackageIdCmp :: PackageId -> PackageId -> Ordering
273 -- ^ Compares package ids lexically, rather than by their 'Unique's
274 stablePackageIdCmp p1 p2 = packageIdFS p1 `compare` packageIdFS p2
275
276 instance Outputable PackageId where
277    ppr pid = text (packageIdString pid)
278
279 instance Binary PackageId where
280   put_ bh pid = put_ bh (packageIdFS pid)
281   get bh = do { fs <- get bh; return (fsToPackageId fs) }
282
283 fsToPackageId :: FastString -> PackageId
284 fsToPackageId = PId
285
286 packageIdFS :: PackageId -> FastString
287 packageIdFS (PId fs) = fs
288
289 stringToPackageId :: String -> PackageId
290 stringToPackageId = fsToPackageId . mkFastString
291
292 packageIdString :: PackageId -> String
293 packageIdString = unpackFS . packageIdFS
294
295
296 -- -----------------------------------------------------------------------------
297 -- $wired_in_packages
298 -- Certain packages are known to the compiler, in that we know about certain
299 -- entities that reside in these packages, and the compiler needs to 
300 -- declare static Modules and Names that refer to these packages.  Hence
301 -- the wired-in packages can't include version numbers, since we don't want
302 -- to bake the version numbers of these packages into GHC.
303 --
304 -- So here's the plan.  Wired-in packages are still versioned as
305 -- normal in the packages database, and you can still have multiple
306 -- versions of them installed.  However, for each invocation of GHC,
307 -- only a single instance of each wired-in package will be recognised
308 -- (the desired one is selected via @-package@\/@-hide-package@), and GHC
309 -- will use the unversioned 'PackageId' below when referring to it,
310 -- including in .hi files and object file symbols.  Unselected
311 -- versions of wired-in packages will be ignored, as will any other
312 -- package that depends directly or indirectly on it (much as if you
313 -- had used @-ignore-package@).
314
315 -- Make sure you change 'Packages.findWiredInPackages' if you add an entry here
316
317 integerPackageId, primPackageId,
318   basePackageId, rtsPackageId, haskell98PackageId,
319   thPackageId, dphSeqPackageId, dphParPackageId,
320   mainPackageId  :: PackageId
321 primPackageId      = fsToPackageId (fsLit "ghc-prim")
322 integerPackageId   = fsToPackageId (fsLit "integer")
323 basePackageId      = fsToPackageId (fsLit "base")
324 rtsPackageId       = fsToPackageId (fsLit "rts")
325 haskell98PackageId = fsToPackageId (fsLit "haskell98")
326 thPackageId        = fsToPackageId (fsLit "template-haskell")
327 dphSeqPackageId    = fsToPackageId (fsLit "dph-seq")
328 dphParPackageId    = fsToPackageId (fsLit "dph-par")
329
330 -- | This is the package Id for the current program.  It is the default
331 -- package Id if you don't specify a package name.  We don't add this prefix
332 -- to symbol names, since there can be only one main package per program.
333 mainPackageId      = fsToPackageId (fsLit "main")
334 \end{code}
335
336 %************************************************************************
337 %*                                                                      *
338 \subsection{@ModuleEnv@s}
339 %*                                                                      *
340 %************************************************************************
341
342 \begin{code}
343 -- | A map keyed off of 'Module's
344 type ModuleEnv elt = FiniteMap Module elt
345
346 emptyModuleEnv       :: ModuleEnv a
347 mkModuleEnv          :: [(Module, a)] -> ModuleEnv a
348 unitModuleEnv        :: Module -> a -> ModuleEnv a
349 extendModuleEnv      :: ModuleEnv a -> Module -> a -> ModuleEnv a
350 extendModuleEnv_C    :: (a->a->a) -> ModuleEnv a -> Module -> a -> ModuleEnv a
351 plusModuleEnv        :: ModuleEnv a -> ModuleEnv a -> ModuleEnv a
352 extendModuleEnvList  :: ModuleEnv a -> [(Module, a)] -> ModuleEnv a
353 extendModuleEnvList_C  :: (a->a->a) -> ModuleEnv a -> [(Module, a)] -> ModuleEnv a
354                   
355 delModuleEnvList     :: ModuleEnv a -> [Module] -> ModuleEnv a
356 delModuleEnv         :: ModuleEnv a -> Module -> ModuleEnv a
357 plusModuleEnv_C      :: (a -> a -> a) -> ModuleEnv a -> ModuleEnv a -> ModuleEnv a
358 mapModuleEnv         :: (a -> b) -> ModuleEnv a -> ModuleEnv b
359 moduleEnvKeys        :: ModuleEnv a -> [Module]
360 moduleEnvElts        :: ModuleEnv a -> [a]
361                   
362 isEmptyModuleEnv     :: ModuleEnv a -> Bool
363 lookupModuleEnv      :: ModuleEnv a -> Module     -> Maybe a
364 lookupWithDefaultModuleEnv :: ModuleEnv a -> a -> Module -> a
365 elemModuleEnv        :: Module -> ModuleEnv a -> Bool
366 foldModuleEnv        :: (a -> b -> b) -> b -> ModuleEnv a -> b
367 filterModuleEnv      :: (a -> Bool) -> ModuleEnv a -> ModuleEnv a
368
369 filterModuleEnv f   = filterFM (\_ v -> f v)
370 elemModuleEnv       = elemFM
371 extendModuleEnv     = addToFM
372 extendModuleEnv_C   = addToFM_C
373 extendModuleEnvList = addListToFM
374 extendModuleEnvList_C = addListToFM_C
375 plusModuleEnv_C     = plusFM_C
376 delModuleEnvList    = delListFromFM
377 delModuleEnv        = delFromFM
378 plusModuleEnv       = plusFM
379 lookupModuleEnv     = lookupFM
380 lookupWithDefaultModuleEnv = lookupWithDefaultFM
381 mapModuleEnv f      = mapFM (\_ v -> f v)
382 mkModuleEnv         = listToFM
383 emptyModuleEnv      = emptyFM
384 moduleEnvKeys       = keysFM
385 moduleEnvElts       = eltsFM
386 unitModuleEnv       = unitFM
387 isEmptyModuleEnv    = isEmptyFM
388 foldModuleEnv f     = foldFM (\_ v -> f v)
389 \end{code}
390
391 \begin{code}
392 -- | A set of 'Module's
393 type ModuleSet = FiniteMap Module ()
394
395 mkModuleSet     :: [Module] -> ModuleSet
396 extendModuleSet :: ModuleSet -> Module -> ModuleSet
397 emptyModuleSet  :: ModuleSet
398 moduleSetElts   :: ModuleSet -> [Module]
399 elemModuleSet   :: Module -> ModuleSet -> Bool
400
401 emptyModuleSet    = emptyFM
402 mkModuleSet ms    = listToFM [(m,()) | m <- ms ]
403 extendModuleSet s m = addToFM s m ()
404 moduleSetElts     = keysFM
405 elemModuleSet     = elemFM
406 \end{code}
407
408 A ModuleName has a Unique, so we can build mappings of these using
409 UniqFM.
410
411 \begin{code}
412 -- | A map keyed off of 'ModuleName's (actually, their 'Unique's)
413 type ModuleNameEnv elt = UniqFM elt
414 \end{code}