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