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