So here's a strawman proposal arising from discussions with Simon on irc
today.

Ghc needs to know quite a bit about gcc to bludgeon it into doing what ghc
wants. Depending on different versions of gcc and on different OSs and
machine arches we need different flags. This presents a problem for users
who upgrade gcc after upgrading ghc since currently ghc only tests gcc at
configure/install time. so we may end up using innapropriate flags for the
cersion of gcc that we're actially using. Add to this that some distros have
special extra features in gcc that often need disabling (eg various
"hardening" features) and we see that the current system is not flexible
enough.

So the idea is to be able to chage these gcc flags later, in particular when
the user changes their gcc version. Distros may be able to automate that to
make it transparent.

Simon suggested that instead of hard-coding these flags into ghc that we put
them in the rts package and that we write a program to re-generate the rts
package configuration. This program would be used at install time and could
be used later to update ghc's gcc settings if the gcc version changes.

So here's a patch that adds a "ghc-reconf" tool. Currently it generates
mostly what rts/package.conf.in produces.

Shortcommings:
        * It uses #ifdefs from ghcconfig.h. It might be nicer if took all
        this information dynamically. So we could generate the
        configuration for any arch/os/gcc combo. Perhaps this is too much
        to ask if it depends on compilcated os-specific configure tests.
        At least the gcc-version specific tests need to be done dynamically
        and not via #ifdefs.

        * I don't quite understand the INSTALLING ifdef logic. Ideally this
        would be replaced with appropriate command line argument(s).

        * it doesn't yet replace any of the options currently set in
        DynFlags:smachdepCCOpts which is where most of the gcc version-
        specific flags actually are currently set.

So if this looks like the right kind of thing then I'll carry on.

Wed May  3 19:06:45 BST 2006  Duncan Coutts <[EMAIL PROTECTED]>
  * Innitial idea for a ghc-reconf tool.

New patches:

[Innitial idea for a ghc-reconf tool.
Duncan Coutts <[EMAIL PROTECTED]>**20060503180645] {
adddir ./utils/ghc-reconf
hunk ./utils/Makefile 9
-SUBDIRS = mkdependC mkdirhier runstdtest genapply genprimopcode ghc-pkg unlit
+SUBDIRS = mkdependC mkdirhier runstdtest genapply genprimopcode ghc-pkg \
+	  ghc-reconf unlit
hunk ./utils/Makefile 12
-SUBDIRS = mkdependC mkdirhier runstdtest ghc-pkg hasktags hp2ps hsc2hs \
-	  parallel prof unlit genprimopcode genapply runghc
+SUBDIRS = mkdependC mkdirhier runstdtest ghc-pkg ghc-reconf hasktags \
+	  hp2ps hsc2hs parallel prof unlit genprimopcode genapply runghc
addfile ./utils/ghc-reconf/Main.hs
hunk ./utils/ghc-reconf/Main.hs 1
+{-# OPTIONS -fglasgow-exts #-}
+-----------------------------------------------------------------------------
+--
+-- (c) The University of Glasgow 2004.
+--
+-- RTS package generation tool
+--
+-----------------------------------------------------------------------------
+
+-- TODO:
+
+module Main (main) where
+
+import Version	( version, targetOS, targetARCH )
+import Distribution.InstalledPackageInfo
+import Distribution.Package
+import Distribution.Version
+import Distribution.License
+
+import Prelude
+
+#include "../../includes/ghcconfig.h"
+
+#if __GLASGOW_HASKELL__ >= 504
+import System.Console.GetOpt
+#else
+import GetOpt
+#endif
+
+import Control.Monad
+import System.Environment ( getArgs, getProgName )
+import System.Exit ( exitWith, ExitCode(..) )
+import System.IO
+import Data.List ( isSuffixOf )
+
+-- -----------------------------------------------------------------------------
+-- Entry point
+
+main :: IO ()
+main = do
+  args <- getArgs
+
+  case getOpt Permute flags args of
+	(cli,_,[]) | FlagHelp `elem` cli -> do
+	   prog <- getProgramName
+	   bye (usageInfo (usageHeader prog) flags)
+	(cli,_,[]) | FlagVersion `elem` cli ->
+	   bye ourCopyright
+	(cli,[],[]) ->
+	   runit cli
+	(_,_,errors) -> do
+           prog <- getProgramName
+	   die (concat errors ++ usageInfo (usageHeader prog) flags)
+
+
+-- -----------------------------------------------------------------------------
+-- Command-line syntax
+
+data Flag
+  = FlagHelp
+  | FlagVersion
+  | FlagArch		String
+  | FlagOS		String
+  | FlagGccVersion	String
+--  | FlagGccHardened
+  deriving Eq
+
+flags :: [OptDescr Flag]
+flags = [
+  Option [] ["arch"] (ReqArg FlagArch "ARCH")
+	"which machine architecture",
+  Option [] ["os"] (ReqArg FlagOS "OS")
+	"which operating system",
+  Option [] ["gcc"] (ReqArg FlagGccVersion "VERSION")
+	"which GCC version",
+  Option ['?'] ["help"] (NoArg FlagHelp)
+	"display this help and exit",
+  Option ['V'] ["version"] (NoArg FlagVersion)
+	"output version information and exit"
+  ]
+
+ourCopyright :: String
+ourCopyright = "RTS package generation tool version " ++ version ++ "\n"
+
+usageHeader :: String -> String
+usageHeader prog = substProg prog $
+  "Usage: $p [OPTION]\n"  ++
+  "    Generate an rts package.conf file with settings for a given\n" ++
+  "    computer architecture, operating system and gcc version\n"
+
+substProg :: String -> String -> String
+substProg _ [] = []
+substProg prog ('$':'p':xs) = prog ++ substProg prog xs
+substProg prog (c:xs) = c : substProg prog xs
+
+-- -----------------------------------------------------------------------------
+-- Do the business
+
+runit :: [Flag] -> IO ()
+runit cli = do
+  
+  let settings =
+        [addUndefSyms
+        ,addDotNetSettings
+        ,addLibDlSettings
+        ,addLibRtSettings
+        ,addLibGmpSettings
+        ,addDebugSettings
+        ,addOSSettings targetOS
+        ,addArchSettings targetARCH
+        ,addGccVersionSettings undefined
+        ]
+ 
+  let packageInfo = foldr1 (.) (reverse settings)
+                    basicRtsInstalledPackageInfo
+          
+  putStrLn (showInstalledPackageInfo packageInfo)
+
+
+basicRtsInstalledPackageInfo :: InstalledPackageInfo
+basicRtsInstalledPackageInfo =
+  emptyInstalledPackageInfo {
+    package = PackageIdentifier "rts"
+                Version {
+                  versionBranch = [1,0],
+                  versionTags = []
+                },
+    license = BSD3,
+    maintainer = "[email protected]",
+    exposed = True,
+
+    hsLibraries = ["HSrts"],
+    
+    extraLibraries = ["m", "dl"],
+    includeDirs = ["/usr/lib64/ghc-6.4.2/include"],
+    includes = ["Stg.h"]
+  }
+
+addUndefSyms :: InstalledPackageInfo -> InstalledPackageInfo
+addUndefSyms pInfo =
+  pInfo {
+    ldOptions = undefSymsLdOptions leadingUnderscore
+  }
+
+undefSymsLdOptions :: Bool -> [String]
+undefSymsLdOptions leadingUnderscore =
+ foldr (\x xs -> "-u":x:xs) [] .
+ (if leadingUnderscore then map ('_':) else id) $
+ ["GHCziBase_Izh_static_info"
+ ,"GHCziBase_Czh_static_info"
+ ,"GHCziFloat_Fzh_static_info"
+ ,"GHCziFloat_Dzh_static_info"
+ ,"GHCziPtr_Ptr_static_info"
+ ,"GHCziWord_Wzh_static_info"
+ ,"GHCziInt_I8zh_static_info"
+ ,"GHCziInt_I16zh_static_info"
+ ,"GHCziInt_I32zh_static_info"
+ ,"GHCziInt_I64zh_static_info"
+ ,"GHCziWord_W8zh_static_info"
+ ,"GHCziWord_W16zh_static_info"
+ ,"GHCziWord_W32zh_static_info"
+ ,"GHCziWord_W64zh_static_info"
+ ,"GHCziStable_StablePtr_static_info"
+ ,"GHCziBase_Izh_con_info"
+ ,"GHCziBase_Czh_con_info"
+ ,"GHCziFloat_Fzh_con_info"
+ ,"GHCziFloat_Dzh_con_info"
+ ,"GHCziPtr_Ptr_con_info"
+ ,"GHCziPtr_FunPtr_con_info"
+ ,"GHCziStable_StablePtr_con_info"
+ ,"GHCziBase_False_closure"
+ ,"GHCziBase_True_closure"
+ ,"GHCziPack_unpackCString_closure"
+ ,"GHCziIOBase_stackOverflow_closure"
+ ,"GHCziIOBase_heapOverflow_closure"
+ ,"GHCziIOBase_NonTermination_closure"
+ ,"GHCziIOBase_BlockedOnDeadMVar_closure"
+ ,"GHCziIOBase_BlockedIndefinitely_closure"
+ ,"GHCziIOBase_Deadlock_closure"
+ ,"GHCziIOBase_NestedAtomically_closure"
+ ,"GHCziWeak_runFinalizzerBatch_closure"]
+
+addDotNetSettings :: InstalledPackageInfo -> InstalledPackageInfo
+addDotNetSettings pInfo
+  | wantDotNetSupport = addLibs ["oleaut32", "ole32", "uuid"] pInfo
+  | otherwise = pInfo
+
+addLibDlSettings :: InstalledPackageInfo -> InstalledPackageInfo
+addLibDlSettings pInfo
+  | haveLibDl = addLibs ["dl"] pInfo
+  | otherwise = pInfo
+
+addLibRtSettings :: InstalledPackageInfo -> InstalledPackageInfo
+addLibRtSettings pInfo 
+  | haveLibRt = addLibs ["rt"] pInfo
+  | otherwise = pInfo
+
+addLibGmpSettings :: InstalledPackageInfo -> InstalledPackageInfo
+addLibGmpSettings pInfo 
+  | haveFrameworkGmp = addFrameworks ["GMP"] pInfo
+  | otherwise        = addLibs ["gmp"] pInfo
+
+addDebugSettings :: InstalledPackageInfo -> InstalledPackageInfo
+addDebugSettings pInfo 
+  | debug && haveLibBfd = addLibs ["bfd", "liberty"] pInfo
+  | otherwise = pInfo
+
+addOSSettings :: String -> InstalledPackageInfo -> InstalledPackageInfo
+addOSSettings "mingw32" pInfo =  addLibs ["wsock32"] pInfo
+
+addOSSettings _ pInfo = pInfo
+
+addArchSettings :: String -> InstalledPackageInfo -> InstalledPackageInfo
+addArchSettings _ pInfo = pInfo
+
+addGccVersionSettings :: Version -> InstalledPackageInfo -> InstalledPackageInfo
+addGccVersionSettings _ pInfo = pInfo
+
+addLibs :: [String] -> InstalledPackageInfo -> InstalledPackageInfo
+addLibs libs pInfo = pInfo { extraLibraries = extraLibraries pInfo ++ libs }
+
+addFrameworks :: [String] -> InstalledPackageInfo -> InstalledPackageInfo
+addFrameworks fs pInfo = pInfo { frameworks = frameworks pInfo ++ fs }
+
+-----------------------------------------------------------------------------
+-- cpp stuff
+
+leadingUnderscore :: Bool
+#ifdef LEADING_UNDERSCORE
+leadingUnderscore = True
+#else
+leadingUnderscore = False
+#endif
+
+haveLibDl :: Bool
+#ifdef HAVE_LIBDL
+haveLibDl = True
+#else
+haveLibDl = False
+#endif
+
+haveLibRt :: Bool
+#ifdef HAVE_LIBRT
+haveLibRt = True
+#else
+haveLibRt = False
+#endif
+
+haveLibBfd :: Bool
+#ifdef HAVE_LIBBFD
+haveLibBfd = True
+#else
+haveLibBfd = False
+#endif
+
+haveFrameworkGmp :: Bool
+#ifdef HAVE_FRAMEWORK_GMP
+haveFrameworkGmp = True
+#else
+haveFrameworkGmp = False
+#endif
+
+wantDotNetSupport :: Bool
+#ifdef WANT_DOTNET_SUPPORT
+wantDotNetSupport = True
+#else
+wantDotNetSupport = False
+#endif
+
+debug :: Bool
+#ifdef DEBUG
+debug = True
+#else
+debug = False
+#endif
+
+
+-----------------------------------------------------------------------------
+
+getProgramName :: IO String
+getProgramName = liftM (`withoutSuffix` ".bin") getProgName
+   where str `withoutSuffix` suff
+            | suff `isSuffixOf` str = take (length str - length suff) str
+            | otherwise             = str
+
+bye :: String -> IO a
+bye s = putStr s >> exitWith ExitSuccess
+
+die :: String -> IO a
+die s = do 
+  hFlush stdout
+  prog <- getProgramName
+  hPutStrLn stderr (prog ++ ": " ++ s)
+  exitWith (ExitFailure 1)
addfile ./utils/ghc-reconf/Makefile
hunk ./utils/ghc-reconf/Makefile 1
+TOP=../..
+include $(TOP)/mk/boilerplate.mk
+
+# hack for ghci-inplace script, see below
+INSTALLING=1
+
+# -----------------------------------------------------------------------------
+# ghc-reconf.bin
+
+SRC_HC_OPTS += -cpp -Wall -fno-warn-name-shadowing -fno-warn-unused-matches
+
+# This causes libghccompat.a to be used:
+include $(GHC_COMPAT_DIR)/compat.mk
+
+# This is required because libghccompat.a must be built with
+# $(GhcHcOpts) because it is linked to the compiler, and hence
+# we must also build with $(GhcHcOpts) here:
+SRC_HC_OPTS += $(GhcHcOpts)
+
+ifeq "$(ghc_ge_504)" "NO"
+SRC_HC_OPTS +=  -package lang -package util -package text
+endif
+
+# On Windows, ghc-reconf is a standalone program
+# ($bindir/ghc-reconf.exe), whereas on Unix it needs a wrapper script
+# to pass the appropriate flag to the real binary
+# ($libexecdir/ghc-reconf.bin) so that it can find package.conf.
+ifeq "$(HOSTPLATFORM)" "i386-unknown-mingw32"
+HS_PROG           = ghc-reconf.exe
+INSTALL_PROGS    += $(HS_PROG)
+else
+HS_PROG           = ghc-reconf.bin
+INSTALL_LIBEXECS += $(HS_PROG)
+endif
+
+# -----------------------------------------------------------------------------=
+# Create the Version.hs file
+
+VERSION_HS = Version.hs
+EXTRA_SRCS += $(VERSION_HS)
+
+boot :: $(VERSION_HS)
+
+Version.hs : Makefile $(TOP)/mk/config.mk
+	@$(RM) -f $(VERSION_HS)
+	@echo "Creating $(VERSION_HS) ... "
+	@echo "module Version where" >>$(VERSION_HS)
+	@echo "version, targetOS, targetARCH :: String" >>$(VERSION_HS)
+	@echo "version    = \"$(ProjectVersion)\"" >> $(VERSION_HS)
+	@echo "targetOS   = \"$(TargetOS_CPP)\"" >> $(VERSION_HS)
+	@echo "targetARCH = \"$(TargetArch_CPP)\"" >> $(VERSION_HS)
+
+DIST_CLEAN_FILES += $(VERSION_HS)
+
+# -----------------------------------------------------------------------------
+# ghc-reconf script
+
+ifeq "$(INSTALLING)" "1"
+ifeq "$(BIN_DIST)"   "1"
+GHCPKGBIN=$$\"\"libexecdir/$(HS_PROG)
+PKGCONF=$$\"\"libdir/package.conf
+else
+GHCPKGBIN=$(libexecdir)/$(HS_PROG)
+PKGCONF=$(libdir)/package.conf
+endif # BIN_DIST
+else
+GHCPKGBIN=$(FPTOOLS_TOP_ABS)/utils/ghc-reconf/$(HS_PROG)
+PKGCONF=$(FPTOOLS_TOP_ABS_PLATFORM)/driver/package.conf.inplace
+endif
+
+ifneq "$(HOSTPLATFORM)" "i386-unknown-mingw32"
+INSTALLED_SCRIPT_PROG  = ghc-reconf-$(ProjectVersion)
+endif
+INPLACE_SCRIPT_PROG    = ghc-reconf-inplace
+
+SCRIPT_OBJS	  = ghc-reconf.sh
+INTERP		  = $(SHELL)
+SCRIPT_SUBST_VARS = GHCPKGBIN PKGCONFOPT
+ifneq "$(HOSTPLATFORM)" "i386-unknown-mingw32"
+INSTALL_SCRIPTS  += $(SCRIPT_PROG)
+endif
+PKGCONFOPT 	  = --global-conf $(PKGCONF)
+
+ifeq "$(INSTALLING)" "1"
+SCRIPT_PROG 	=  $(INSTALLED_SCRIPT_PROG)
+ifneq "$(HOSTPLATFORM)" "i386-unknown-mingw32"
+LINK 		=  ghc-reconf
+endif
+else
+SCRIPT_PROG 	=  $(INPLACE_SCRIPT_PROG)
+endif
+
+# -----------------------------------------------------------------------------
+# don't recurse on 'make install'
+#
+ifeq "$(INSTALLING)" "1"
+all :: $(HS_PROG)
+	$(MAKE) INSTALLING=0 BIN_DIST=0 $(MFLAGS) $@
+clean distclean maintainer-clean ::
+	$(MAKE) INSTALLING=0 BIN_DIST=0 $(MFLAGS) $@
+endif
+
+# ghc-reconf is needed to boot in rts/ and library dirs
+# Do a recursive 'make all' after generating dependencies, because this
+# will work with 'make -j'.
+ifneq "$(BootingFromHc)" "YES"
+boot :: depend
+	$(MAKE) all
+endif
+
+include $(TOP)/mk/target.mk
addfile ./utils/ghc-reconf/ghc-reconf.sh
hunk ./utils/ghc-reconf/ghc-reconf.sh 1
+# Mini-driver for ghc-pkg
+exec $GHCPKGBIN ${1+"$@"}
}

Context:

[$(ProjectNameShort) => ghc
Simon Marlow <[EMAIL PROTECTED]>**20060503102419] 
[only pass -fno-unit-at-a-time to gcc if it is supported
Simon Marlow <[EMAIL PROTECTED]>**20060503093614] 
[Arrange that -fth is no longer implied by -fglasgow-exts
[EMAIL PROTECTED]
 
 Messages involving Template Haskell are deeply puzzling
 if you don't know about TH, so it seems better to make
 -fth an explicit flag.  It is no longer switched on
 by -fglasgow-exts.
 
] 
[remove code not required in the new source tree layout
Simon Marlow <[EMAIL PROTECTED]>**20060502114235] 
[move "compat" earlier in the build for .hc bootstrapping
Simon Marlow <[EMAIL PROTECTED]>**20060502112001] 
[fix ctime_r problem on Solaris (I hope)
Simon Marlow <[EMAIL PROTECTED]>**20060502111231] 
[fix whitespace problem that shows up on Solaris (x86)
Simon Marlow <[EMAIL PROTECTED]>**20060502110001] 
[libraries/time is boring
Simon Marlow <[EMAIL PROTECTED]>**20060502105524] 
[add time package to libraries Makefile
Ashley Yakeley <[EMAIL PROTECTED]>**20060501092241] 
[add time package to default-packages
Ashley Yakeley <[EMAIL PROTECTED]>**20060426070445] 
[Fix stage2 segfault on openbsd.
[EMAIL PROTECTED]
 
 Somewhere along the 6.5 branch, gcc started compiling the rts such that
 it triggers the stack smash handler, causing stage2 to by kill'd
 immediately. This turns off the stack protector, which will do for now.
 
] 
[fix quoting around ${FPTOOLS_TOP_ABS} (fixes #749)
Simon Marlow <[EMAIL PROTECTED]>**20060428085252] 
[Fix bug shown in the mod77 test.
Lemmih <[EMAIL PROTECTED]>**20060427113313] 
[Don't init root pointers if they aren't gonna be used.
Lemmih <[EMAIL PROTECTED]>**20060426111143] 
[Fix recompilation checking.
Simon Marlow <[EMAIL PROTECTED]>**20060425140932
 One-shot compilation was throwing away the old iface read by
 checkOldIface, with the result that version numbers were never being
 incremented.  Fixes the recomp001 test too.
] 
[Solaris needs -lrt for the threaded RTS
Simon Marlow <[EMAIL PROTECTED]>**20060425082823] 
[fix problem with binary-dist docs
Simon Marlow <[EMAIL PROTECTED]>**20060424090159] 
[Enable breakpoint support.
Lemmih <[EMAIL PROTECTED]>**20060421113112] 
[Fixing some lexer errors with extcore
Josef Svenningsson <[EMAIL PROTECTED]>**20060420222625] 
[Extcore can now handle data types without constructors
Josef Svenningsson <[EMAIL PROTECTED]>**20060420213622] 
[Comments only
Josef Svenningsson <[EMAIL PROTECTED]>**20060420213555] 
[Resurrect ProjectName
[EMAIL PROTECTED] 
[Remove the section on platform support, link to the wiki page
Simon Marlow <[EMAIL PROTECTED]>**20060420125555
 The section in the building guide was becoming out of date, a wiki
 page is much more likely to be kept fresh.
] 
[Fix workaround for a GHC 6.4 bug
[EMAIL PROTECTED] 
[hslibs is dead, Jim...
[EMAIL PROTECTED] 
[Synched .spec file with reality
[EMAIL PROTECTED] 
[Add .spec file to source distribution
[EMAIL PROTECTED] 
[remove paragraph about mutable objects that doesn't apply now
Simon Marlow <[EMAIL PROTECTED]>**20060419082038] 
[HsBool should be HsInt, not StgBool
Simon Marlow <[EMAIL PROTECTED]>**20060418144214
 StgBool is mapped to C's int type.  GHC doesn't currently know the
 size of a C int on the target arch, it's easier to use StgInt instead.
 I guess nobody ever uses Bool arguments to foreign imports/exports.
] 
[handle Bool arg to foreign import "wrapper"
Simon Marlow <[EMAIL PROTECTED]>**20060418143936
 Fixes #746
] 
[update commentry for foreign import "wrapper" handling
Simon Marlow <[EMAIL PROTECTED]>**20060418143714] 
[remove vestiges of ByteArray and MutableByteArray, which are no more
Simon Marlow <[EMAIL PROTECTED]>**20060418143641] 
[Comment only
[EMAIL PROTECTED] 
[Fix rank-validity testing
[EMAIL PROTECTED]
 
 GHC does not now do "hoisting" as it used to.  Instead, it allows
 foralls to the right of fuction arrows, as well as to the left.
 
 But the type-validity tester hadn't caught up.  This commit fixes 
 it. The test is tc203.
 
 Incidentally, GHC still doesn't let you write
 	forall a. Eq a => forall b. b -> b
 because we get a zillion reduce/reduce errors if we allow that.  I'm
 sure it's fixable.  But meanwhile you have to use an auxiliary type
 synonym, which is a bit stupid.
 
 
] 
[Make the initial rdr and type scope available in the ghc-api.
Lemmih <[EMAIL PROTECTED]>**20060418023606] 
[Fix minor bug in Linker.withExtendedLinkEnv
Lemmih <[EMAIL PROTECTED]>**20060418023518] 
[Export 'insertSymbol' and 'insertStableSymbol'.
Lemmih <[EMAIL PROTECTED]>**20060418021806
 
 'insertStableSymbol' is used for exporting closures that are affected by the GC.
 
] 
[Allow $x, as well as $(x), at top level in TH
[EMAIL PROTECTED]
 
 Bulat pointed out that in Template Haskell
    $x
 is allowed instead of 
    $(x)
 in expressions, but not at the top level of modules.
 
 This commit fixes the omission.  Now you can say
 
 	f x = x
  	$h
 	data T = T
 
 and the $h will run Template Haskell just as you'd expect.
 
] 
[Fix TH erorr recovery (test is TH_recover)
[EMAIL PROTECTED] 
[Comments only
[EMAIL PROTECTED] 
[Recover gracefully from a Template Haskell programmers error
[EMAIL PROTECTED]
 
 If a TH programmer uses a type constructor as a data constructor,
 GHC simply crashed.  This commit makes it report the error in a
 graceful way.
 
] 
[Document newtype-unwrapping for IO in FFI
[EMAIL PROTECTED] 
[Cosmetics in SpecConstr
[EMAIL PROTECTED]
 
 SpecConstr currently uses substExpr for tiresome reasons to do with
 GADTs.  Unfortunately the substExpr generates some WARNINGS (when DEBUG)
 is on, because we aren't adding all the in-scope Ids to the in-scope
 set of the substitution.
 
 When we move to FC these substExprs will go away, so I'm not going to
 worry about this now.
 
] 
[Improve pruning of case alternatives to account for GADTs
[EMAIL PROTECTED]
 
 Consider
 
   data T a where
     T1 :: T Int
     T2 :: T Bool
     T3 :: T Char
 
   f :: T Bool -> Int
   f x = case x of
 	  DEFAULT -> ...
 	  T2 -> 3
 
 Here the DEFAULT case covers multiple constructors (T1,T3), but none 
 of them can match a scrutinee of type (T Bool).  So we can prune away
 the default case altogether.
 
 In implementing this, I re-factored this bit of the simplifier, elminiating
 prepareAlts from SimplUtils, and putting all the work into simplAlts in
 Simplify
 
 The proximate cause was a program written by Manuel using PArrays
 
] 
[Fix a bug in optimising division to shift right
Simon Marlow <[EMAIL PROTECTED]>**20060412144247
 Division by an integral log2 can't be directly optimised to a shift
 right, because shift right behaves like a division that rounds to
 negative infinity, whereas we want one that rounds to zero.  Fix this
 by adding (divisor-1) to the dividend when it is negative before
 shifting.  We do this without jumps, generating very slightly worse
 code than gcc, which uses conditional moves on CPUs that support it.
] 
[Omit lndir on Windows, as it used to be
[EMAIL PROTECTED] 
[remove a trace
Simon Marlow <[EMAIL PROTECTED]>**20060411131531] 
[Allow IO to be wrapped in a newtype in foreign import/export
[EMAIL PROTECTED]
 
 Up to now, the silent unwrapping of newtypes in foreign import/export
 has been limited to data values.  But it's useful for the IO monad
 itself:
 
 	newtype MyIO a = MIO (IO a)
 
 	foreign import foo :: Int -> MyIO Int
 
 This patch allows the IO monad to be
 wrapped too. This applies to foreign import "dynamic" and "wrapper", 
 thus
    foreign import "wrapper" foo :: MyIO () -> HisIO (FunPtr (MyIO ())) 
 
 Warning: I did on the plane, and I'm no longer sure if its 100% 
 complete, so needs more testing.  In particular the wrapper/dynamic bit.
 
] 
[Improve newtype deriving
[EMAIL PROTECTED]
 
 Ross Paterson pointed out a useful generalisation of GHC's 
 newtype-deriving mechanism.  This implements it.  The idea
 is to allow
 	newtype Wrap m a = Wrap (m a) deriving (Monad, Eq)
 where the representation type doesn't start with a type
 constructor.
 
 Actually GHC already *did* implement this, but the eta-ok
 check in TcDeriv missed a case, so there was a lurking bug.
 
 This patches fixes the documentation too.  drvrun019 tests.
 
 
] 
[add take to the list of functions deforestable
Simon Marlow <[EMAIL PROTECTED]>**20060411090131] 
[avoid versionitis in Numeric.showHex (should fix tcrun007)
Simon Marlow <[EMAIL PROTECTED]>**20060411085009] 
[add a note about full-laziness
Simon Marlow <[EMAIL PROTECTED]>**20060410093824] 
[robustify the test for the top of the tree a little
Simon Marlow <[EMAIL PROTECTED]>**20060410082224] 
[Make darcs-all work without a ghc toplevel directory
Josef Svenningsson <[EMAIL PROTECTED]>**20060407161738] 
[Fix typo in darcsall warning
Josef Svenningsson <[EMAIL PROTECTED]>**20060407161335] 
[fix source dists
Simon Marlow <[EMAIL PROTECTED]>**20060407150045] 
[add a README for binary dists
Simon Marlow <[EMAIL PROTECTED]>**20060407143832] 
[fix binary dists
Simon Marlow <[EMAIL PROTECTED]>**20060407143822] 
[remove the last bits of the ghc/ subdir
Simon Marlow <[EMAIL PROTECTED]>**20060407085219] 
[TAG 07.04.06
Lemmih <[EMAIL PROTECTED]>**20060407130411] 
Patch bundle hash:
de58cac80316e520aedba01bdab1a4e457275908
_______________________________________________
Cvs-ghc mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to