summaryrefslogtreecommitdiff
path: root/ghc/compiler/codeGen/CgMonad.lhs
diff options
context:
space:
mode:
authorsimonmar <unknown>2004-11-26 16:22:13 +0000
committersimonmar <unknown>2004-11-26 16:22:13 +0000
commitef5b4b146aa172d8ac10f39b5eb3d7a0f948d8f1 (patch)
treeccf398dd86fd64e8034098b39f47e610885d88cd /ghc/compiler/codeGen/CgMonad.lhs
parent1f8b341a88b6b60935b0ce80b59ed6e356b8cfbf (diff)
downloadhaskell-ef5b4b146aa172d8ac10f39b5eb3d7a0f948d8f1.tar.gz
[project @ 2004-11-26 16:19:45 by simonmar]
Further integration with the new package story. GHC now supports pretty much everything in the package proposal. - GHC now works in terms of PackageIds (<pkg>-<version>) rather than just package names. You can still specify package names without versions on the command line, as long as the name is unambiguous. - GHC understands hidden/exposed modules in a package, and will refuse to import a hidden module. Also, the hidden/eposed status of packages is taken into account. - I had to remove the old package syntax from ghc-pkg, backwards compatibility isn't really practical. - All the package.conf.in files have been rewritten in the new syntax, and contain a complete list of modules in the package. I've set all the versions to 1.0 for now - please check your package(s) and fix the version number & other info appropriately. - New options: -hide-package P sets the expose flag on package P to False -ignore-package P unregisters P for this compilation For comparison, -package P sets the expose flag on package P to True, and also causes P to be linked in eagerly. -package-name is no longer officially supported. Unofficially, it's a synonym for -ignore-package, which has more or less the same effect as -package-name used to. Note that a package may be hidden and yet still be linked into the program, by virtue of being a dependency of some other package. To completely remove a package from the compiler's internal database, use -ignore-package. The compiler will complain if any two packages in the transitive closure of exposed packages contain the same module. You *must* use -ignore-package P when compiling modules for package P, if package P (or an older version of P) is already registered. The compiler will helpfully complain if you don't. The fptools build system does this. - Note: the Cabal library won't work yet. It still thinks GHC uses the old package config syntax. Internal changes/cleanups: - The ModuleName type has gone away. Modules are now just (a newtype of) FastStrings, and don't contain any package information. All the package-related knowledge is in DynFlags, which is passed down to where it is needed. - DynFlags manipulation has been cleaned up somewhat: there are no global variables holding DynFlags any more, instead the DynFlags are passed around properly. - There are a few less global variables in GHC. Lots more are scheduled for removal. - -i is now a dynamic flag, as are all the package-related flags (but using them in {-# OPTIONS #-} is Officially Not Recommended). - make -j now appears to work under fptools/libraries/. Probably wouldn't take much to get it working for a whole build.
Diffstat (limited to 'ghc/compiler/codeGen/CgMonad.lhs')
-rw-r--r--ghc/compiler/codeGen/CgMonad.lhs26
1 files changed, 17 insertions, 9 deletions
diff --git a/ghc/compiler/codeGen/CgMonad.lhs b/ghc/compiler/codeGen/CgMonad.lhs
index f6b209672a..d9d0801a03 100644
--- a/ghc/compiler/codeGen/CgMonad.lhs
+++ b/ghc/compiler/codeGen/CgMonad.lhs
@@ -1,7 +1,7 @@
%
% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
%
-% $Id: CgMonad.lhs,v 1.41 2004/09/10 14:53:47 simonmar Exp $
+% $Id: CgMonad.lhs,v 1.42 2004/11/26 16:20:10 simonmar Exp $
%
\section[CgMonad]{The code generation monad}
@@ -47,7 +47,7 @@ module CgMonad (
Sequel(..), -- ToDo: unabstract?
-- ideally we wouldn't export these, but some other modules access internal state
- getState, setState, getInfoDown,
+ getState, setState, getInfoDown, getDynFlags,
-- more localised access to monad state
getStkUsage, setStkUsage,
@@ -61,6 +61,7 @@ module CgMonad (
import {-# SOURCE #-} CgBindery ( CgBindings, nukeVolatileBinds )
+import CmdLineOpts ( DynFlags )
import Cmm
import CmmUtils ( CmmStmts, isNopStmt )
import CLabel
@@ -75,6 +76,8 @@ import UniqSupply ( UniqSupply, mkSplitUniqSupply, splitUniqSupply, uniqFromSupp
import FastString
import Outputable
+import Control.Monad ( liftM )
+
infixr 9 `thenC` -- Right-associative!
infixr 9 `thenFC`
\end{code}
@@ -92,6 +95,7 @@ along.
\begin{code}
data CgInfoDownwards -- information only passed *downwards* by the monad
= MkCgInfoDown {
+ cgd_dflags :: DynFlags,
cgd_mod :: Module, -- Module being compiled
cgd_statics :: CgBindings, -- [Id -> info] : static environment
cgd_srt :: CLabel, -- label of the current SRT
@@ -99,9 +103,10 @@ data CgInfoDownwards -- information only passed *downwards* by the monad
cgd_eob :: EndOfBlockInfo -- Info for stuff to do at end of basic block:
}
-initCgInfoDown :: Module -> CgInfoDownwards
-initCgInfoDown mod
- = MkCgInfoDown { cgd_mod = mod,
+initCgInfoDown :: DynFlags -> Module -> CgInfoDownwards
+initCgInfoDown dflags mod
+ = MkCgInfoDown { cgd_dflags = dflags,
+ cgd_mod = mod,
cgd_statics = emptyVarEnv,
cgd_srt = error "initC: srt",
cgd_ticky = mkTopTickyCtrLabel,
@@ -370,11 +375,11 @@ instance Monad FCode where
The Abstract~C is not in the environment so as to improve strictness.
\begin{code}
-initC :: Module -> FCode a -> IO a
+initC :: DynFlags -> Module -> FCode a -> IO a
-initC mod (FCode code)
+initC dflags mod (FCode code)
= do { uniqs <- mkSplitUniqSupply 'c'
- ; case code (initCgInfoDown mod) (initCgState uniqs) of
+ ; case code (initCgInfoDown dflags mod) (initCgState uniqs) of
(res, _) -> return res
}
@@ -499,6 +504,9 @@ newUnique = do
getInfoDown :: FCode CgInfoDownwards
getInfoDown = FCode $ \info_down state -> (info_down,state)
+getDynFlags :: FCode DynFlags
+getDynFlags = liftM cgd_dflags getInfoDown
+
withInfoDown :: FCode a -> CgInfoDownwards -> FCode a
withInfoDown (FCode fcode) info_down = FCode $ \_ state -> fcode info_down state
@@ -646,7 +654,7 @@ forkEvalHelp :: EndOfBlockInfo -- For the body
a) -- Result of the FCode
-- A disturbingly complicated function
forkEvalHelp body_eob_info env_code body_code
- = do { info_down@(MkCgInfoDown cg_info statics srt ticky _) <- getInfoDown
+ = do { info_down <- getInfoDown
; us <- newUniqSupply
; state <- getState
; let { info_down_for_body = info_down {cgd_eob = body_eob_info}