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