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