Wed Aug  2 18:59:22 BST 2006  Duncan Coutts <[EMAIL PROTECTED]>
  * Try to support TH with profiling. See ticket #91.
  This needs testing.

Fri Aug 18 02:04:49 BST 2006  Duncan Coutts <[EMAIL PROTECTED]>
  * Add xargs function and use it when linking.
  When using GHC's --split-objs we end up with lots of files to link.
  This can mean overflowing the maximum length of the command line
  when invoking ar or ld. On windows the maximum length is 32k. On
  other systems it's not a great deal more. GHC currently deals with
  this problem by using xargs. This patch does more or less the same.
New patches:

[Try to support TH with profiling. See ticket #91.
Duncan Coutts <[EMAIL PROTECTED]>**20060802175922
 This needs testing.
] {
hunk ./Distribution/Simple/GHC.hs 101
-      ifVanillaLib = when (forceVanillaLib || withVanillaLib lbi)
-        where forceVanillaLib = False
-              --TODO: we may need to force the vanilla libs to build as it may
-              -- be that TemplateHaskell needs the vanilla libs even when
-              -- building profiling libs. See:
-              -- http://www.haskell.org/pipermail/template-haskell/2003-July/000135.html
-              --
-              -- So we might need something like this:
-              --
-              -- forceVanillaLib = elem TemplateHaskell (extensions libBi)
-
+      ifVanillaLib forceVanilla = when (forceVanilla || withVanillaLib lbi)
hunk ./Distribution/Simple/GHC.hs 120
+	  forceVanillaLib = TemplateHaskell `elem` extensions libBi
+	  -- TH always needs vanilla libs, even when building for profiling
hunk ./Distribution/Simple/GHC.hs 140
-        do ifVanillaLib (rawSystemExit verbose ghcPath ghcArgs)
+        do ifVanillaLib forceVanillaLib (rawSystemExit verbose ghcPath ghcArgs)
hunk ./Distribution/Simple/GHC.hs 200
-        ifVanillaLib (rawSystemPathExit verbose "ar" arArgs)
+        ifVanillaLib forceVanillaLib (rawSystemPathExit verbose "ar" arArgs)
hunk ./Distribution/Simple/GHC.hs 242
-                 let binArgs = 
+                 let binArgs linkExe profExe =
hunk ./Distribution/Simple/GHC.hs 244
-                         ++ ["-I"++pref,
-                             "-o", targetDir `joinFileName` exeName'
-                            ]
+                         ++ ["-I"++pref]
+			 ++ (if linkExe
+			        then ["-o", targetDir `joinFileName` exeName']
+                                else ["-c"])
hunk ./Distribution/Simple/GHC.hs 254
-                         ++ if withProfExe lbi
+                         ++ if profExe
hunk ./Distribution/Simple/GHC.hs 257
-                 rawSystemExit verbose ghcPath binArgs
+
+		 -- For building exe's for profiling that use TH we actually
+		 -- have to build twice, once without profiling and the again
+		 -- with profiling. This is because the code that TH needs to
+		 -- run at compile time needs to be the vanilla ABI so it can
+		 -- be loaded up and run by the compiler.
+		 when (withProfExe lbi && TemplateHaskell `elem` extensions exeBi)
+		    (rawSystemExit verbose ghcPath (binArgs False False))
+
+		 rawSystemExit verbose ghcPath (binArgs True (withProfExe lbi))
}

[Add xargs function and use it when linking.
Duncan Coutts <[EMAIL PROTECTED]>**20060818010449
 When using GHC's --split-objs we end up with lots of files to link.
 This can mean overflowing the maximum length of the command line
 when invoking ar or ld. On windows the maximum length is 32k. On
 other systems it's not a great deal more. GHC currently deals with
 this problem by using xargs. This patch does more or less the same.
] {
hunk ./Distribution/Simple/GHC.hs 54
-import Distribution.Simple.Utils( rawSystemExit, rawSystemPathExit, die,
-				  dirOf, moduleToFilePath,
+import Distribution.Simple.Utils( rawSystemExit, rawSystemPath,
+				  rawSystemVerbose, maybeExit, xargs,
+				  die, dirOf, moduleToFilePath,
hunk ./Distribution/Simple/GHC.hs 80
-import System.Directory		( removeFile, getDirectoryContents,
-				  doesFileExist )
+import System.Directory		( removeFile, renameFile,
+				  getDirectoryContents, doesFileExist )
+import System.Exit              (ExitCode(..))
hunk ./Distribution/Simple/GHC.hs 189
-		++ hObjs
+            arObjArgs =
+		   hObjs
hunk ./Distribution/Simple/GHC.hs 195
-		++ hProfObjs
+            arProfObjArgs =
+		   hProfObjs
hunk ./Distribution/Simple/GHC.hs 200
-	        ++ ["-o", ghciLibName]
-		++ hObjs
+	        ++ ["-o", ghciLibName `joinFileExt` "tmp"]
+            ldObjArgs =
+		   hObjs
hunk ./Distribution/Simple/GHC.hs 205
-        ifVanillaLib forceVanillaLib (rawSystemPathExit verbose "ar" arArgs)
-        ifProfLib (rawSystemPathExit verbose "ar" arProfArgs)
+
hunk ./Distribution/Simple/GHC.hs 207
-        let (compilerDir, _) = splitFileName $ compilerPath (compiler lbi)
+            (compilerDir, _) = splitFileName $ compilerPath (compiler lbi)
hunk ./Distribution/Simple/GHC.hs 210
-        ifGHCiLib (rawSystemExit verbose ld ldArgs)
+            rawSystemLd = rawSystemVerbose
+            maxCommandLineSize = 32 * 1024
hunk ./Distribution/Simple/GHC.hs 213
-        ifGHCiLib (rawSystemPathExit verbose "ld" ldArgs)
+            ld = "ld"
+            rawSystemLd = rawSystemPath
+             --TODO: discover this at configure time on unix
+            maxCommandLineSize = 32 * 1024
hunk ./Distribution/Simple/GHC.hs 218
+            runLd ld args = do
+              exists <- doesFileExist ghciLibName
+              status <- rawSystemLd verbose ld
+                          (args ++ if exists then [ghciLibName] else [])
+              when (status == ExitSuccess)
+                   (renameFile (ghciLibName `joinFileExt` "tmp") ghciLibName)
+              return status
+
+        ifVanillaLib False $ maybeExit $ xargs maxCommandLineSize
+          (rawSystemPath verbose) "ar" arArgs arObjArgs
+
+        ifProfLib $ maybeExit $ xargs maxCommandLineSize
+          (rawSystemPath verbose) "ar" arProfArgs arProfObjArgs
+
+        ifGHCiLib $ maybeExit $ xargs maxCommandLineSize
+          runLd ld ldArgs ldObjArgs
hunk ./Distribution/Simple/Utils.hs 52
+        xargs,
hunk ./Distribution/Simple/Utils.hs 90
-import Data.List (nub)
+import Data.List (nub, unfoldr)
hunk ./Distribution/Simple/Utils.hs 173
+-- | Like the unix xargs program. Useful for when we've got very long command
+-- lines that might overflow an OS limit on command line length and so you
+-- need to invoke a command multiple times to get all the args in.
+--
+-- Use it with either of the rawSystem variants above. For example:
+-- 
+-- > xargs (32*1024) (rawSystemPath verbose) prog fixedArgs bigArgs
+--
+xargs :: Int -> (FilePath -> [String] -> IO ExitCode)
+      -> FilePath -> [String] -> [String] -> IO ExitCode
+xargs maxSize rawSystem prog fixedArgs bigArgs =
+  let fixedArgSize = sum (map length fixedArgs)
+      chunkSize = maxSize - fixedArgSize
+      loop [] = return ExitSuccess
+      loop (args:remainingArgs) = do
+        status <- rawSystem prog (fixedArgs ++ args)
+        case status of
+          ExitSuccess -> loop remainingArgs
+          _           -> return status
+   in loop (chunks chunkSize bigArgs)
+
+  where chunks len = unfoldr $ \s ->
+          if null s then Nothing
+                    else Just (chunk [] len s)
+
+        chunk acc len []     = (reverse acc,[])
+        chunk acc len (s:ss)
+          | len' < len = chunk (s:acc) (len-len'-1) ss
+          | otherwise  = (reverse acc, s:ss)
+          where len' = length s
}

Context:

[repair Distribution.Compat.Map for non-GHC
Ross Paterson <[EMAIL PROTECTED]>**20060810124314] 
[Avoid use of deprecated Data.FiniteMap, if possible
Simon Marlow <[EMAIL PROTECTED]>**20060809153232
 Distribution.Compat.Map taken from Haddock.
] 
[Change 'getInstalledPkg' to the more sensible 'getLatestPkg'.
Lemmih <[EMAIL PROTECTED]>**20060806135545] 
[Don't check for packagesDirName and servListFile, they may not exist.
Lemmih <[EMAIL PROTECTED]>**20060806135423] 
[GHC build only: set $(MKDEPENDHS) in addition to $(HC)
Simon Marlow <[EMAIL PROTECTED]>**20060803092216] 
[pass the whole packageId to GHC with the -package-name flag
Simon Marlow <[EMAIL PROTECTED]>**20060720150931
 This shouldn't make any difference to current GHC's, but will be
 required by the new GHC package code.
] 
[install: pass the verbose flag to register too
Simon Marlow <[EMAIL PROTECTED]>**20060728085914] 
[Add documentation of new LocalBuildInfo fields
Duncan Coutts <[EMAIL PROTECTED]>**20060726230130] 
[Wrap excessively long line
Duncan Coutts <[EMAIL PROTECTED]>**20060726221702] 
[Hold back on forcing vanilla libs for TH for the moment
Duncan Coutts <[EMAIL PROTECTED]>**20060726221532
 When we get confirmation from GHC devs that it's the right
 thing to do then we can add it in.
] 
[Add initial support for --enable/disable-library-vanilla flags
[EMAIL PROTECTED]
 For additional information see these mail threads:
 
 http://www.haskell.org//pipermail/libraries/2006-July/005522.html
 http://urchin.earth.li/pipermail/debian-haskell/2006-July/000220.html
] 
[build and install cabal-setup as part of GHC build
Simon Marlow <[EMAIL PROTECTED]>**20060720140417] 
[fix indentation in do block for H'98 compatibility
[EMAIL PROTECTED] 
[resolve conflicts from henning-thielemann's work.  Thanks Henning!
[EMAIL PROTECTED] 
[install Haddock documentation in share/package/doc/html and register that path in the ghc-pkg
[EMAIL PROTECTED] 
[PackageDescription: haddockName generates the name of the .haddock file
[EMAIL PROTECTED] 
[PackageDescription: added toMaybe, some logical simplifications
[EMAIL PROTECTED] 
[Distribution.Simple.Utils: copyDirectoryRecursiveVerbose
[EMAIL PROTECTED] 
[Distribution.Compat.Directory: added getDirectoryContentsWithoutSpecial
[EMAIL PROTECTED] 
[Distribution.simple: haddock option --use-package tells which packages to hyperlink to
[EMAIL PROTECTED] 
[stripPrefix -> dropPrefix
[EMAIL PROTECTED] 
[generate .haddock interface file when running haddock
[EMAIL PROTECTED] 
[UNDO: Merge "unrecognized long opt" fix from 6.4.2
Simon Marlow <[EMAIL PROTECTED]>**20060705142842
 This patch undid the previous patch, "merge from base".  I asked Sven
 to revert it, but didn't get an answer.
   
 See GHC bug #473.
] 
[finish interaction with remote HTTP servers
[EMAIL PROTECTED] 
[stage 2 patch: implement the "list" command
[EMAIL PROTECTED] 
[it's now 00-latest not latest
[EMAIL PROTECTED] 
[implement support for flat-file layout
[EMAIL PROTECTED] 
[parsec is not a dependency
Simon Marlow <[EMAIL PROTECTED]>**20060518131434
 It is apparently required for the wash2hs test, however.
] 
[Merge "unrecognized long opt" fix from 6.4.2
Sven Panne <[EMAIL PROTECTED]>**20060506110640] 
[Cabal.xml: entity greencard was mixed up with haddock
[EMAIL PROTECTED] 
[Change flags passed to hsc2hs
Duncan Coutts <[EMAIL PROTECTED]>**20060704001926
 The extra-libraries must be passed as -L-l${lib} or linking the C prog
 that hsc2hs generates may fail if any symbols are referenced.
 Also can't use cppOptions function since hsc2hs doesn't support -U.
 Need to do -U flags in ccOptions seperately.
] 
[Hugs: copy paths module to the right place, this time
Ross Paterson <[EMAIL PROTECTED]>**20060503132510] 
[pass correct -P flag to ffihugs
Ross Paterson <[EMAIL PROTECTED]>**20060503122452
 
 The -P flag wasn't superfluous, but it was wrong for executables.
] 
[Hugs: copy path module into package build dir
Ross Paterson <[EMAIL PROTECTED]>**20060503122300] 
[add header file for GetModuleFileNameA
Ross Paterson <[EMAIL PROTECTED]>**20060502141641] 
[remove superfluous ffihugs -P option
Ross Paterson <[EMAIL PROTECTED]>**20060502104635] 
[fix for Hugs
Ross Paterson <[EMAIL PROTECTED]>**20060502101054
 
 Add explicit types for a couple of constants to work around Hugs's
 imperfect implementation of the monomorphism restriction.
] 
[Change calls to 'make' into '$(MAKE)'
Duncan Coutts <[EMAIL PROTECTED]>**20060502174630
 This is the portable thing to do and fixes things on FreeBSD where make/=gmake
] 
[TAG 1.1.4
[EMAIL PROTECTED] 
[TAG shipped in GHC 6.4.2
Simon Marlow <[EMAIL PROTECTED]>**20060424093133] 
[Hugs: also compile the paths module
Ross Paterson <[EMAIL PROTECTED]>**20060501171206] 
[markup fix
Ross Paterson <[EMAIL PROTECTED]>**20060501145015] 
[move cabal-install/etc-cabal-get to cabal-install/etc-cabal-install
[EMAIL PROTECTED] 
[Complete move of cabal-get to cabal-install + some fixups
[EMAIL PROTECTED] 
[basic information for installing
[EMAIL PROTECTED] 
[build and install cabal-setup
[EMAIL PROTECTED] 
[add etc-cabal-get as a data-file
[EMAIL PROTECTED] 
[bumping cabal version number. 1.1.4 will be the one released with ghc 6.4.2.
[EMAIL PROTECTED] 
[modify makefile for cabal-install
[EMAIL PROTECTED] 
[cabal-get will become cabal-install
[EMAIL PROTECTED] 
[getting rid of cabal-install in favor of cabal-get
[EMAIL PROTECTED] 
[Remove erroneous exports...
[EMAIL PROTECTED] 
[Patch to fix "-ixyz" being overwritten by "-i" and to remove Cabal's dependency on the Cabal package.
[EMAIL PROTECTED] 
[Separate build into "make build" and "make install"
[EMAIL PROTECTED] 
[Fixups to get cabal-get into Cabal
[EMAIL PROTECTED] 
[Update Cabal with cabal-get
[EMAIL PROTECTED] 
[Fix JHC command lines.
Einar Karttunen <ekarttun@cs.helsinki.fi>**20060427005922] 
[document install-includes and register --inplace
Simon Marlow <[EMAIL PROTECTED]>**20060428130542] 
[fix imports for Windows
[EMAIL PROTECTED] 
[Better support for packages that need to install header files
Simon Marlow <[EMAIL PROTECTED]>**20060426140627
 
 There's a new field for .cabal files: 
 
      install-includes: foo.h bar.h
 
 This means the same as 'includes', except that the files named therein
 will be installed into $libdir/include.  'includes' should only be
 used for headers already installed on the system.
 
 Directories listed in 'include-dirs' still turn into -I options for
 hsc2hs, cpphs, and C compilations.  However, for installation
 purposes, relative directories in 'include-dirs' are now treated
 differently from absolute directories:
 
   - an absolute directory is copied to the include-dirs field
     of the installed package config
 
   - files names in install-includes are assumed to be found in
     one of the *relative* directories listed in include-dirs
 
 So the common pattern for providing a header file that you want to
 be available everywhere including to via-C compilations against this
 package:
 
   include-dirs: myincludes
   install-includes: foo.h
 
 will install the header file myincludes/foo.h in
 $libdir/include/foo.h.
] 
[merge from base:
Simon Marlow <[EMAIL PROTECTED]>**20060426121408
 
 Wed Apr 26 13:11:10 BST 2006  Simon Marlow <[EMAIL PROTECTED]>
   * RequireOrder: do not collect unrecognised options after a non-opt
] 
[pass unrecognised options before the command name to the command
Simon Marlow <[EMAIL PROTECTED]>**20060426121321
 Previously, options before the command name other than --help were
 just ignored, which is quite confusing behaviour.  So now,
 
 ./setup --with-compiler=ghc-6.4.2 configure
 
 works as you expect, instead of ignoring the --with-compiler option.
] 
[First attempt at a cabal-setup command
Simon Marlow <[EMAIL PROTECTED]>**20060303162233
 cabal-setup is a replacement for 'runhaskell Setup.hs'.  It accepts
 exactly the same commands.  Additionally, the following new features
 are provided:
 
  * Setup.{hs,lhs} is optional.  If omitted, cabal-setup behaves just
    like Distribution.Simple.defaultMain.
 
  * If the .cabal file contains a cabal-version field, then Setup.hs
    is built using an appropriate version of Cabal.  This might entail
    creating Setup.hs if it doesn't exist.
 
  * cabal-setup interprets the options --with-compiler and --with-hc-pkg
    to determine the compiler used to compile Setup.hs.
 
 Later, we could add support for building multiple packages in
 dependency order, as per recent discussions on [EMAIL PROTECTED]
] 
[add new modules
Ross Paterson <[EMAIL PROTECTED]>**20060425195548] 
[Implement "setup register --inplace", and a few other minor things
Simon Marlow <[EMAIL PROTECTED]>**20060425144733
  
 There are a few changes in this patch:
  
    - New flag to register, --inplace.  "setup register --inplace"
      registers the package for use in the build tree, i.e. without
      installing.  It works with GHC only, currently.
      
    - The parameters to RegisterCmd, UnregisterCmd and InstallCmd are a
      legacy from before the time of hooks (or something) and don't
      serve any purpose any more, AFAICT.  So I removed them.
  
    - I don't think "setup register" worked propertly before if
      --user was given to configure.  It does now.
 
    - New flag to register: --with-hc-pkg (just the same as when
      given to configure, but lets you override it at register-time)
] 
[Refactoring only: separate compiler-specific simple build implementation
Simon Marlow <[EMAIL PROTECTED]>**20060425111957] 
[get LocalBuildInfo from Distribution.LocalBuildInfo
Simon Marlow <[EMAIL PROTECTED]>**20060425111921] 
[warning cleanup
Simon Marlow <[EMAIL PROTECTED]>**20060425102302] 
[Distribution.Compat.FilePath should be hidden
Simon Marlow <[EMAIL PROTECTED]>**20060411141305
 This also matches package.conf.in.
] 
[Hide Distribution.GetOpt; it just re-exports System.Console.GetOpt anyway
Simon Marlow <[EMAIL PROTECTED]>**20060411141045
 This also matches Cabal.cabal.
] 
[GHC FFI flag should be -fffi not -ffi, the latter merely happens to work.
Duncan Coutts <[EMAIL PROTECTED]>**20060318022010] 
[Make ghc-6.2 packages be exposed by default.
Duncan Coutts <[EMAIL PROTECTED]>**20060221135026
 For ghc-6.4 when Cabal registers packages it exposes them by default.
 However it does not do the same fo ghc-6.2. This change corrects the
 discrepancy. This patch is already being used in Gentoo with Cabal 1.1.3.
] 
[test case for buildinfo with multiple executables
[EMAIL PROTECTED] 
[It is no longer necessary to run 'configure' before 'clean' or 'sdist', addressing http://haskell.galois.com/trac/hackage/ticket/12.
Nick Alexander <[EMAIL PROTECTED]>**20060404054127
 In order to change this behaviour, it was necessary to modify the hook interface, specifically cleanHook, postClean, sDistHook, postSDist.  They now take a Maybe LocalBuildInfo, since a LocalBuildInfo might not be available in .setup-config.
] 
[windows patch from [EMAIL PROTECTED]
[EMAIL PROTECTED] 
[oops, don't enable -split-objs by default
Simon Marlow <[EMAIL PROTECTED]>**20060314124358] 
[export configDependency
Simon Marlow <[EMAIL PROTECTED]>**20060303155527] 
[comment fix
Simon Marlow <[EMAIL PROTECTED]>**20060303155516] 
[don't check cabal-version during parsing, it doesn't work
Simon Marlow <[EMAIL PROTECTED]>**20060303155500
 because parsers are evaluated multiple times due to backtracking.
] 
[no need to use a verbatim copy of System.Console.GetOpt, omit if possible
Simon Marlow <[EMAIL PROTECTED]>**20060303144025] 
[Support for -split-objs with GHC
Simon Marlow <[EMAIL PROTECTED]>**20060302170907
 New configure option: --enable-split-objs creates libraries using
 -split-objs with GHC (current HEAD or later only, the configure checks
 for version 6.5).  Fixes ticket #19.
] 
[Initial support for JHC
Einar Karttunen <ekarttun@cs.helsinki.fi>**20060206233543] 
[added some fields to test suite for duncan's mods
[EMAIL PROTECTED] 
[fixup PackageDescription test code
Duncan Coutts <[EMAIL PROTECTED]>**20060201183912
 just ignore the extra ParseOk warnings field
] 
[ignore "x-" extension fields without a warning
Duncan Coutts <[EMAIL PROTECTED]>**20060201183145] 
[Make unknown fields a warning rather than an error
Duncan Coutts <[EMAIL PROTECTED]>**20060201182944
 Add support for warnings to the ParseResult type. Change existing
 warnings from using Debug.Trace to use this new warning support.
] 
[fix conflict
Simon Marlow <[EMAIL PROTECTED]>**20060206095833] 
[push and pull all
[EMAIL PROTECTED] 
[combine GNUmakefile and Makefile
Simon Marlow <[EMAIL PROTECTED]>**20060206095400] 
[now build Setup.lhs instead of using runghc on it. still uses runhugs.
[EMAIL PROTECTED] 
[cabal-install uses defaultMain if it can't find Setup.lhs
[EMAIL PROTECTED] 
[cleaned up suffix handler params to hooks
[EMAIL PROTECTED]
 
 Summary if last few changes: I modified the hooks interface quite a
 bit, again.  There's good news and bad news about this.  The good news
 is that it's cleaned up and should be easier to maintain and to avoid
 future modifications.  The bad news is that this change itself will
 break stuff, of course.
 
 If you have any trouble building your Setup scripts, please let me
 know.  I really think that it was best to bite the bullet right now in
 one big go instead of down the road with lots of little changes.  I
 have a lot more confidence in the hooks interface, and I don't
 actually expect that it'll change as often.
 
 I made the types more consistent, and made sure there are accessor
 functions on each of the Flags types so that if the flags types change
 in the future, it shouldn't break lots of code.
 
 Another piece of good / bad news is that I decided not to get rid of
 the pre & post hooks.  They are nice for convenience and it wouldn't
 be nearly so easy to write hooks without them.
 
 That's bad because the interface to hooks is still pretty big, which
 means that there's more likelihood that it'll change in the future.
 
 Another weakness in the Hooks interface is that with command hooks
 (like sDistHook) it's tempting to add parameters to them; basically
 the stuff that we compute between the preSDist and sDist hook.  I
 removed such params and have their values computed elsewhere.
 
 Cabal hackers, please avoid adding parameters to these command hooks
 if at all possible in order to keep the interface steady.  If you need
 to compute a value to pass to these functions, compute it in the
 function and / or make it available as a function that someone
 crafting hooks can use as well, or consider whether it belongs in one
 of the parameters already being passed to the hooks,
 PackageDescription, LocalBuildInfo, UserHooks, Flags.
 
] 
[make the order of params to cmd hooks consistent
[EMAIL PROTECTED] 
[remove some flags from sdist, some cleanup
[EMAIL PROTECTED] 
[clarifying and making flags types consistent
[EMAIL PROTECTED] 
[changing tuple types to records w/ fields
[EMAIL PROTECTED] 
[moving TODO stuff to wiki
[EMAIL PROTECTED] 
[fix version number in fptools makefile to match .cabal file
[EMAIL PROTECTED] 
[Add extraGHCiLibraries to the InstalledPackageInfo and extend the parser.
Duncan Coutts <[EMAIL PROTECTED]>**20060131163640] 
[re-add the GNUmakefiles
Simon Marlow <[EMAIL PROTECTED]>*-20060123115236
 These are now safe after we added "-f Makefile" to the make args when invoked
 from the GHC build system.  This repo should now be useable as the main
 Cabal repo.
] 
[re-add the GNUmakefiles
Simon Marlow <[EMAIL PROTECTED]>**20060123115236
 These are now safe after we added "-f Makefile" to the make args when invoked
 from the GHC build system.  This repo should now be useable as the main
 Cabal repo.
] 
[TAG checkpoint
[EMAIL PROTECTED] 
Patch bundle hash:
0d8a0c232fee0214a6352e6a2922a256a78ab07c
_______________________________________________
cabal-devel mailing list
cabal-devel@haskell.org
http://www.haskell.org/mailman/listinfo/cabal-devel

Reply via email to