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