Simon,

Ultimately I'd like to cabal do the dependency analysis, be able to
rebuild any module (not just the lib/prog target) and do things like
parallel builds.

I'm well aware however that no one has the time at the moment to address
that.

Duncan

On Fri, 2007-03-09 at 16:07 +0000, Simon Marlow wrote:
> I'm sending this patch here to solicit comments.
> 
> Ian Lynagh has been converting GHC's build system to use Cabal for packages 
> instead of our current Makefile setup.  There are a couple of things that 
> don't 
> work as well with Cabal: (1) we can't use 'make -j' and get parallel builds, 
> and 
> (2) we can't build individual files and give extra options on the command 
> line: 
> this is occasionally very useful when debugging the compiler or testing small 
> changes.
> 
> So we could fix these with brute force: I have patches to make GHC --make 
> work 
> in parallel, but it needs a lot of work to make it robust.  We could add 
> support 
> to Cabal to build a single file and give extra options on the command line, 
> but 
> most people don't need this.
> 
> Instead, I decided to address both of these in one go: the idea is to have 
> Cabal 
> generate a Makefile that you can use with 'make -j' or to build a single file 
> with 'make dist/build/Foo.o', for example.  It only works with GHC, and only 
> for 
> libraries (I could probably make it work for executables too, just haven't 
> done 
> that yet).  It does work with profiling, and as far as I can tell everything 
> else works, because GHC gets invoked with almost exactly the same arguments 
> as 
> with 'setup build', except that it is invoked one file at a time.
> 
> This is really the missing piece needed to let GHC use Cabal for its build 
> system, so I'm pretty keen for this to go in.  Comments?
> 
> Cheers,
>       Simon
> plain text document attachment (setup-makefile.patch)
> New patches:
> 
> [Add 'setup makefile' command
> Simon Marlow <[EMAIL PROTECTED]>**20070309155022
>  'setup makefile' generates a Makefile that performs the steps
>  necessary to compile the Haskell sources to object code.  This only
>  works for libraries, and only with GHC right now.
>  
>  Instead of simply 'setup build', you can do this:
>  
>    $ ./setup makefile
>    $ make
>    $ ./setup build
>  
>  where './setup makefile' does the preprocessing and generates a
>  Makefile tailored to the current package.  'make' will build all the
>  Haskell code to object files, and 'setup build' will build any C code
>  and the library archives.
>  
>  The reason for all this is that you can say 'make -j' and get a
>  parallel build, or you can say
>  
>    make dist/build/Foo.o EXTRA_HC_OPTS=-keep-s-file
>  
>  to compile a single file with extra options.
> ] {
> hunk ./Distribution/Make.hs 172
> +
> +            MakefileCmd -> exitWith ExitSuccess -- presumably nothing to do
> hunk ./Distribution/Setup.hs 52
> +                           MakefileFlags(..), emptyMakefileFlags,
> hunk ./Distribution/Setup.hs 62
> +                           parseMakefileArgs,
> hunk ./Distribution/Setup.hs 97
> +            | MakefileCmd             -- makefile
> hunk ./Distribution/Setup.hs 253
> +
> +data MakefileFlags = MakefileFlags {makefileVerbose :: Int,
> +                                    makefileFile :: Maybe FilePath}
> +    deriving Show
> +emptyMakefileFlags = MakefileFlags {makefileVerbose = 1,
> +                                    makefileFile = Nothing}
> +
> hunk ./Distribution/Setup.hs 263
> --- |Most of these flags are for Configure, but InstPrefix is for Copy.
> +-- | All the possible flags
> hunk ./Distribution/Setup.hs 302
> +          -- For makefile:
> +          | MakefileFile FilePath
> hunk ./Distribution/Setup.hs 391
> -commandList progConf = [(configureCmd progConf), buildCmd, cleanCmd, 
> installCmd,
> +commandList progConf = [(configureCmd progConf), buildCmd, makefileCmd,
> +                        cleanCmd, installCmd,
> hunk ./Distribution/Setup.hs 609
> +makefileCmd :: Cmd a
> +makefileCmd = Cmd {
> +        cmdName        = "makefile",
> +        cmdHelp        = "Perform any necessary makefileing.",
> +        cmdDescription = "",  -- This can be a multi-line description
> +        cmdOptions     = [cmd_help, cmd_verbose,
> +           Option "f" ["file"] (reqPathArg MakefileFile)
> +               "Filename to use (default: Makefile)."],
> +        cmdAction      = MakefileCmd
> +        }
> +
> +parseMakefileArgs :: MakefileFlags -> [String] -> [OptDescr a] -> IO 
> (MakefileFlags, [a], [String])
> +parseMakefileArgs = parseArgs makefileCmd updateCfg
> +  where updateCfg mflags fl =
> +           case fl of
> +                Verbose n      -> mflags{makefileVerbose=n}
> +                MakefileFile f -> mflags{makefileFile=Just f}
> +
> hunk ./Distribution/Simple/Build.hs 46
> -     build
> +     build, makefile
> hunk ./Distribution/Simple/Build.hs 58
> -import Distribution.Setup     (CopyDest(..), BuildFlags(..) )
> +import Distribution.Setup    ( CopyDest(..), BuildFlags(..), 
> +                                  MakefileFlags(..) )
> hunk ./Distribution/Simple/Build.hs 75
> -import Control.Monad                 ( unless )
> +import Control.Monad                 ( unless, when )
> hunk ./Distribution/Simple/Build.hs 92
> -build :: PackageDescription  -- ^mostly information from the .cabal file
> +build    :: PackageDescription  -- ^mostly information from the .cabal file
> hunk ./Distribution/Simple/Build.hs 98
> +  initialBuildSteps pkg_descr lbi verbose suffixes
> +  setupMessage verbose "Building" pkg_descr
> +  case compilerFlavor (compiler lbi) of
> +    GHC  -> GHC.build  pkg_descr lbi verbose
> +    JHC  -> JHC.build  pkg_descr lbi verbose
> +    Hugs -> Hugs.build pkg_descr lbi verbose
> +    _    -> die ("Building is not supported with this compiler.")
> +
> +makefile :: PackageDescription  -- ^mostly information from the .cabal file
> +         -> LocalBuildInfo -- ^Configuration information
> +         -> MakefileFlags -- ^Flags that the user passed to makefile
> +         -> [ PPSuffixHandler ] -- ^preprocessors to run before compiling
> +         -> IO ()
> +makefile pkg_descr lbi flags suffixes = do
> +  let verb = makefileVerbose flags
> +  initialBuildSteps pkg_descr lbi verb suffixes
> +  when (not (hasLibs pkg_descr)) $
> +      die ("Makefile is only supported for libraries, currently.")
> +  setupMessage verb "Generating Makefile" pkg_descr
> +  case compilerFlavor (compiler lbi) of
> +    GHC  -> GHC.makefile  pkg_descr lbi flags
> +    _    -> die ("Generating a Makefile is not supported for this compiler.")
> +
> +
> +initialBuildSteps pkg_descr lbi verbose suffixes = do
> hunk ./Distribution/Simple/Build.hs 138
> -  setupMessage verbose "Building" pkg_descr
> -  case compilerFlavor (compiler lbi) of
> -   GHC  -> GHC.build  pkg_descr lbi verbose
> -   JHC  -> JHC.build  pkg_descr lbi verbose
> -   Hugs -> Hugs.build pkg_descr lbi verbose
> -   _    -> die ("Building is not supported with this compiler.")
> hunk ./Distribution/Simple/GHC.hs 5
> --- Copyright   :  Isaac Jones 2003-2006
> +-- Copyright   :  Isaac Jones 2003-2007
> hunk ./Distribution/Simple/GHC.hs 47
> -     build, installLib, installExe
> +     build, makefile, installLib, installExe
> hunk ./Distribution/Simple/GHC.hs 50
> +import Distribution.Setup       ( MakefileFlags(..) )
> hunk ./Distribution/Simple/GHC.hs 90
> +import System.IO
> hunk ./Distribution/Simple/GHC.hs 355
> -     ++ (if compilerVersion (compiler lbi) > Version [6,4] []
> +     ++ ghcOptions lbi bi odir
> +
> +ghcOptions lbi bi odir
> +     =  (if compilerVersion (compiler lbi) > Version [6,4] []
> hunk ./Distribution/Simple/GHC.hs 378
> +-- 
> -----------------------------------------------------------------------------
> +-- Building a Makefile
> +
> +makefile :: PackageDescription -> LocalBuildInfo -> MakefileFlags -> IO ()
> +makefile pkg_descr lbi flags = do
> +  let file = case makefileFile flags of
> +                Just f ->  f
> +                _otherwise -> "Makefile"
> +  h <- openFile file WriteMode
> +
> +  let Just lib = library pkg_descr
> +      bi = libBuildInfo lib
> +  
> +      ghc_vers = compilerVersion (compiler lbi)
> +      packageId | versionBranch ghc_vers >= [6,4]
> +                                = showPackageId (package pkg_descr)
> +                 | otherwise = pkgName (package pkg_descr)
> +  let decls = [
> +        ("modules", unwords (exposedModules lib ++ otherModules bi)),
> +        ("GHC", compilerPath (compiler lbi)),
> +        ("WAYS", if withProfLib lbi then "p" else ""),
> +        ("odir", buildDir lbi),
> +        ("package", packageId),
> +        ("GHC_OPTS", unwords (ghcOptions lbi bi (buildDir lbi))),
> +        ("MAKEFILE", file)
> +        ]
> +  hPutStrLn h (unlines (map (\(a,b)-> a ++ " = " ++ munge b) decls))
> +  hPutStrLn h makefileTemplate
> +  hClose h
> + where
> +  munge "" = ""
> +  munge ('#':s) = '\\':'#':munge s
> +  munge (c:s) = c : munge s
> +
> hunk ./Distribution/Simple/GHC.hs 497
> +-- 
> -----------------------------------------------------------------------------
> +-- Makefile template
> +
> +makefileTemplate =
> + "GHC_OPTS += -package-name $(package) -i$(odir)\n"++
> + "\n"++
> + "# For adding options on the command-line\n"++
> + "GHC_OPTS += $(EXTRA_HC_OPTS)\n"++
> + "\n"++
> + "WAY_p_OPTS = -prof\n"++
> + "\n"++
> + "ifneq \"$(way)\" \"\"\n"++
> + "way_ := $(way)_\n"++
> + "_way := _$(way)\n"++
> + "GHC_OPTS += $(WAY_$(way)_OPTS)\n"++
> + "GHC_OPTS += -hisuf $(way_)hi -hcsuf $(way_)hc -osuf $(way_)o\n"++
> + "endif\n"++
> + "\n"++
> + "OBJS = $(patsubst %,$(odir)/%.$(way_)o,$(subst .,/,$(modules)))\n"++
> + "\n"++
> + "all :: .depend $(OBJS)\n"++
> + "\n"++
> + ".depend : $(MAKEFILE)\n"++
> + "   $(GHC) -M -optdep-f -optdep.depend $(foreach way,$(WAYS),-optdep-s 
> -optdep$(way)) $(foreach obj,$(MKDEPENDHS_OBJ_SUFFICES),-osuf $(obj)) 
> $(filter-out -split-objs, $(GHC_OPTS)) $(modules)\n"++
> + "   for dir in $(sort $(foreach mod,$(OBJS),$(dir $(mod)))); do \\\n"++
> + "           if test ! -d $$dir; then mkdir $$dir; fi \\\n"++
> + "   done\n"++
> + "\n"++
> + "include .depend\n"++
> + "\n"++
> + "# suffix rules\n"++
> + "\n"++
> + "ifneq \"$(odir)\" \"\"\n"++
> + "odir_ = $(odir)/\n"++
> + "else\n"++
> + "odir_ =\n"++
> + "endif\n"++
> + "\n"++
> + "$(odir_)%.$(way_)o : %.hs\n"++
> + "   $(GHC) $(GHC_OPTS) -c $< -o $@  -ohi $(basename $@).$(way_)hi\n"++
> + "\n"++
> + "$(odir_)%.$(way_)o : %.lhs  \n"++
> + "   $(GHC) $(GHC_OPTS) -c $< -o $@  -ohi $(basename $@).$(way_)hi\n"++
> + "\n"++
> + "$(odir_)%.$(way_)o : %.c\n"++
> + "   @$(RM) [EMAIL PROTECTED]"++
> + "   $(GHC) $(GHC_CC_OPTS) -c $< -o [EMAIL PROTECTED]"++
> + "\n"++
> + "$(odir_)%.$(way_)o : %.$(way_)s\n"++
> + "   @$(RM) [EMAIL PROTECTED]"++
> + "   $(GHC) $(GHC_CC_OPTS) -c $< -o [EMAIL PROTECTED]"++
> + "\n"++
> + "$(odir_)%.$(way_)o : %.S\n"++
> + "   @$(RM) [EMAIL PROTECTED]"++
> + "   $(GHC) $(GHC_CC_OPTS) -c $< -o [EMAIL PROTECTED]"++
> + "\n"++
> + "$(odir_)%.$(way_)s : %.c\n"++
> + "   @$(RM) [EMAIL PROTECTED]"++
> + "   $(GHC) $(GHC_CC_OPTS) -S $< -o [EMAIL PROTECTED]"++
> + "\n"++
> + "%.$(way_)hi : %.$(way_)o\n"++
> + "   @if [ ! -f $@ ] ; then \\\n"++
> + "       echo Panic! $< exists, but $@ does not.; \\\n"++
> + "       exit 1; \\\n"++
> + "   else exit 0 ; \\\n"++
> + "   fi                                                      \n"++
> + "\n"++
> + "%.$(way_)hi-boot : %.$(way_)o-boot\n"++
> + "   @if [ ! -f $@ ] ; then \\\n"++
> + "       echo Panic! $< exists, but $@ does not.; \\\n"++
> + "       exit 1; \\\n"++
> + "   else exit 0 ; \\\n"++
> + "   fi                                                      \n"++
> + "\n"++
> + "$(odir_)%.$(way_)hi : %.$(way_)hc\n"++
> + "   @if [ ! -f $@ ] ; then \\\n"++
> + "       echo Panic! $< exists, but $@ does not.; \\\n"++
> + "       exit 1; \\\n"++
> + "   else exit 0 ; \\\n"++
> + "   fi\n"++
> + "\n"++
> + "show:\n"++
> + "   @echo '$(VALUE)=\"$($(VALUE))\"'\n"++
> + "\n"++
> + "\n"++
> + "ifneq \"$(strip $(WAYS))\" \"\"\n"++
> + "ifeq \"$(way)\" \"\"\n"++
> + "all ::\n"++
> + "# Don't rely on -e working, instead we check exit return codes from 
> sub-makes.\n"++
> + "   @case '${MFLAGS}' in *-[ik]*) x_on_err=0;; *-r*[ik]*) x_on_err=0;; *) 
> x_on_err=1;; esac; \\\n"++
> + "   for i in $(WAYS) ; do \\\n"++
> + "     echo \"== $(MAKE) way=$$i -f $(MAKEFILE) $@;\"; \\\n"++
> + "     $(MAKE) way=$$i -f $(MAKEFILE) --no-print-directory $(MFLAGS) $@ ; 
> \\\n"++
> + "     if [ $$? -eq 0 ] ; then true; else exit $$x_on_err; fi; \\\n"++
> + "   done\n"++
> + "   @echo \"== Finished recursively making \\`$@' for ways: $(WAYS) 
> ...\"\n"++
> + "endif\n"++
> + "endif\n"++
> + "\n"++
> + "# We could consider adding this: the idea would be to have 'make' do\n"++
> + "# everything that 'setup build' does.\n"++
> + "# ifeq \"$(way)\" \"\"\n"++
> + "# all ::\n"++
> + "#  ./Setup build\n"++
> + "# endif\n"
> +
> hunk ./Distribution/Simple.hs 80
> -import Distribution.Simple.Build     ( build )
> +import Distribution.Simple.Build     ( build, makefile )
> hunk ./Distribution/Simple.hs 157
> +      -- |Hook to run before makefile command.  Second arg indicates 
> verbosity level.
> +     preMakefile  :: Args -> MakefileFlags -> IO HookedBuildInfo,
> +
> +     -- |Over-ride this hook to gbet different behavior during makefile.
> +     makefileHook :: PackageDescription -> LocalBuildInfo -> Maybe UserHooks 
> -> MakefileFlags -> IO (),
> +      -- |Hook to run after makefile command.  Second arg indicates 
> verbosity level.
> +     postMakefile :: Args -> MakefileFlags -> PackageDescription -> 
> LocalBuildInfo -> IO ExitCode,
> +
> hunk ./Distribution/Simple.hs 324
> +            MakefileCmd ->
> +                command (parseMakefileArgs emptyMakefileFlags) 
> makefileVerbose
> +                        preMakefile makefileHook postMakefile
> +                        getPersistBuildConfig
> +        
> hunk ./Distribution/Simple.hs 603
> +       preMakefile = rn,
> +       makefileHook = ru,
> +       postMakefile = res,
> hunk ./Distribution/Simple.hs 642
> +       makefileHook = defaultMakefileHook,
> hunk ./Distribution/Simple.hs 675
> +       preMakefile = readHook makefileVerbose,
> hunk ./Distribution/Simple.hs 726
> +      writeInstalledConfig pkg_descr localbuildinfo False
> +
> +defaultMakefileHook :: PackageDescription -> LocalBuildInfo
> +     -> Maybe UserHooks -> MakefileFlags -> IO ()
> +defaultMakefileHook pkg_descr localbuildinfo hooks flags = do
> +  makefile pkg_descr localbuildinfo flags (allSuffixHandlers hooks)
> +  when (hasLibs pkg_descr) $
> hunk ./doc/Cabal.xml 1704
> +
> +    <sect2 id="setup-makefile">
> +      <title>setup makefile</title>
> +      <para>Generate a Makefile that may be used to compile the
> +      Haskell modules to object code.  This command is currently only
> +      supported when building libraries, and only if the compiler is
> +      GHC.</para>
> +
> +      <para>The makefile replaces part of the work done by
> +      <literal>setup build</literal>.  The sequence of commands would
> +      typeically be:
> +<programlisting>
> +runhaskell Setup.hs makefile
> +make
> +runhaskell Setup.hs build
> +</programlisting>
> +      where <literal>setup makefile</literal> does the preprocessing,
> +      <literal>make</literal> compiles the Haskell modules, and
> +      <literal>setup build</literal> performs any final steps, such as
> +      building the library archives.</para>
> +
> +      <para>The Makefile does not use GHC's <literal>--make</literal>
> +      flag to compile the modules, instead it compiles modules one at
> +      a time, using dependency information generated by GHC's
> +      <literal>-M</literal> flag.  There are two reasons you might
> +      therefore want to use <literal>setup makefile</literal>:
> +
> +      <itemizedlist>
> +        <listitem>
> +          <para>You want to build in parallel using <literal>make 
> -j</literal>.
> +          Currently, <literal>setup build</literal> on its own does not 
> support
> +          building in parallel.</para>
> +        </listitem>
> +        <listitem>
> +          <para>You want to build an individual module, pass extra
> +          flags to a compilation, or do other non-standard things that
> +          <literal>setup build</literal> does not support.</para>
> +        </listitem>
> +      </itemizedlist>
> +      </para>
> +
> +    </sect2>
> }
> 
> Context:
> 
> [add Distribution.SetupWrapper to exposed-modules
> Simon Marlow <[EMAIL PROTECTED]>**20070309122146] 
> [Tweaks to make Cabal play nicer with haddock
> Ian Lynagh <[EMAIL PROTECTED]>**20070308155718
>  
>  The path for the html docs now includes the package name at the end,
>  which works nicer for multiple packages sharing a contents/index.
>  
>  Use --ghc-pkg when available (in haddock darcs only currently) to tell
>  haddock which ghc-pkg to use.
>  
>  Use --allow-missing-html when available (in haddock darcs only
>  currently) to tell haddock not to worry if it can't find the HTML for
>  packages we depend on. This is necessary when haddocking a group of
>  packages before moving them all into place.
> ] 
> [Cope with ghc-pkg telling us packages are broken
> Ian Lynagh <[EMAIL PROTECTED]>**20070307193131] 
> [Tell GHC to use .hs mode when we want it to cpp something for us
> Ian Lynagh <[EMAIL PROTECTED]>**20070307143612] 
> [Add parentheses so expressions are parsed correctly
> Ian Lynagh <[EMAIL PROTECTED]>**20070307131941] 
> [minor refactoring
> Ross Paterson <[EMAIL PROTECTED]>**20070301002731] 
> [fix \begin{code typo
> Ross Paterson <[EMAIL PROTECTED]>**20070301002557] 
> [document the --with-compiler / --with-hc inconsistency
> Ross Paterson <[EMAIL PROTECTED]>**20070225115601] 
> [Clarify documentation on --with-compiler and --with-hc-pkg
> [EMAIL PROTECTED] 
> [minor markup tweaks
> Ross Paterson <[EMAIL PROTECTED]>**20070218104622] 
> [This usePackages stuff is haddock-specific so name it as such
> Duncan Coutts <[EMAIL PROTECTED]>**20070213201434] 
> [{en,dis}able-use-packages, -optP-P only if haddock<0.8
> Conal Elliott <[EMAIL PROTECTED]>**20070204061106] 
> [cabal-upload: Added command-line options for username, password, checking 
> instead of uploading. Added ability to get login from file, and to get 
> password from the terminal. Added still unused verbosity options. Bumped 
> version number to 0.2.
> [EMAIL PROTECTED] 
> [exclude Setup.lhs
> Ross Paterson <[EMAIL PROTECTED]>**20070212193608
>  
>  This was generating a useless Main entry in the lib doc index.
>  (good for STABLE)
> ] 
> [Add recent Cabal modules to nhc98 build system.
> [EMAIL PROTECTED] 
> [Compatibility with Haskell'98.
> [EMAIL PROTECTED]
>  Import Distribution.Compat.Exception instead of Control.Exception.
>  Fix illegal indentation of cascaded do-blocks.
> ] 
> [add --enable-optimization/--disable-optimization config options (on by 
> default)
> Ross Paterson <[EMAIL PROTECTED]>**20070212004513] 
> [cabal-upload: nicer output.
> [EMAIL PROTECTED] 
> [Send Accept header.
> [EMAIL PROTECTED] 
> [Allow uploading multiple packages.
> [EMAIL PROTECTED] 
> [Changed HTTP dependency to >= 1.0. 
> [EMAIL PROTECTED] 
> [cabal-upload: Removed build-simple since hackage doesn't seem to accept it 
> for non-lib packages.
> [EMAIL PROTECTED] 
> [Added URL for cabal-upload wiki page.
> [EMAIL PROTECTED] 
> [Added usage message to cabal-upload.
> [EMAIL PROTECTED] 
> [Added a small hacky first version of cabal-upload.
> [EMAIL PROTECTED] 
> [cabal-setup doesn't need -cpp
> Ross Paterson <[EMAIL PROTECTED]>**20070115154724] 
> [Refactorings only
> Simon Marlow <[EMAIL PROTECTED]>**20070114203741
>  Here are a batch of refactorings to clean up parsing and parts of the
>  simple build system.  This patch originated in a patch sent to
>  cabal-devel@haskell.org with an intial implementation of
>  configurations.  Since then we decided to go a different route with
>  configurations, so I have separated the refactoring from the
>  configurations patch.
>  
>  At this point, 2 tests fail for me, but I get the same 2 failures
>  without this patch.
> ] 
> [pass arguments through when performing the setup actions ourselves
> Ross Paterson <[EMAIL PROTECTED]>**20070113133211] 
> [separate option for the compiler for Setup.hs
> Ross Paterson <[EMAIL PROTECTED]>**20070113133000
>  
>  This need not be the same compiler as used to build the package
> ] 
> [Ignoring user packages when installing locally doesn't make sense.
> Lemmih <[EMAIL PROTECTED]>**20070112150318] 
> [cabal-install now caches downloaded packages in the directory for the 
> package, and with .tar.gz extension.
> [EMAIL PROTECTED] 
> [cabal-install.cabal: Added build-type field. Change hs-source-dir to 
> hs-source-dirs (hs-source-dir has been deprecated for some time).
> [EMAIL PROTECTED] 
> [cabal-install --user now keeps package cache and package list in 
> ~/.cabal-install
> [EMAIL PROTECTED] 
> [fix ghc-options (not a listField)
> [EMAIL PROTECTED] 
> [add a Build-Type field, and use it in setupWrapper
> Ross Paterson <[EMAIL PROTECTED]>**20070111233018
>  
>  As discussed on the libraries list (Nov 2006), add a field Build-Type
>  which can be used to declare that this package uses one of the boilerplate
>  setup scripts.  This allows setupWrapper (used by cabal-setup and
>  cabal-install) to bypass the setup script in this case and perform
>  the setup actions itself.
> ] 
> [remove a use of null+head
> Ross Paterson <[EMAIL PROTECTED]>**20070111182430] 
> [remove two fromJust's
> Ross Paterson <[EMAIL PROTECTED]>**20070111182401] 
> [pass CABAL_VERSION to Hugs
> Ross Paterson <[EMAIL PROTECTED]>**20070111182216] 
> [cabal-install now puts the package list in /var/lib/cabal-install and the 
> tarballs in /var/cache/cabal-install by default. Added command-line options 
> for changing those.
> [EMAIL PROTECTED] 
> [Track verbosity argument changes
> Ian Lynagh <[EMAIL PROTECTED]>**20070111180601] 
> [Testsuite quietening
> Ian Lynagh <[EMAIL PROTECTED]>**20070111175329] 
> [cabal-install: Output usage info for the right command when pasrsing the 
> package name arguments fails.
> [EMAIL PROTECTED] 
> [SetupWrapper now passes verbosity to other functions, as required by Igloo's 
> patch.
> [EMAIL PROTECTED] 
> [Make cabal-install use setupWrapper (the library version of cabal-setup).
> [EMAIL PROTECTED] 
> [Moved the cabal-setup code to Distribution.SetupWrapper, so that 
> cabal-install can use it. CabalSetup.hs now just calls the setupWrapper 
> function.
> [EMAIL PROTECTED] 
> [Quieten the testsuite more
> Ian Lynagh <[EMAIL PROTECTED]>**20070111155957] 
> [Pass verbosity info down to warn
> Ian Lynagh <[EMAIL PROTECTED]>**20070111154526] 
> [Derive Show on various datatypes
> Ian Lynagh <[EMAIL PROTECTED]>**20070111140220] 
> [Give feedback in runTests.sh
> Ian Lynagh <[EMAIL PROTECTED]>**20070111132654] 
> [Be less verbose at verbosity level 1
> Ian Lynagh <[EMAIL PROTECTED]>**20070111131228] 
> [Fix warning
> Ian Lynagh <[EMAIL PROTECTED]>**20070111130928] 
> [No need for -fno-warn-unused-matches any more
> Ian Lynagh <[EMAIL PROTECTED]>**20070111130824] 
> [Always pass Hooks around, not Maybe Hooks
> Ian Lynagh <[EMAIL PROTECTED]>**20070111124234] 
> [Make Makefile use the right ghc/ghc-pkg
> Ian Lynagh <[EMAIL PROTECTED]>**20070111122833] 
> [Add -Wall to GHCFLAGS
> Ian Lynagh <[EMAIL PROTECTED]>**20070111102742] 
> [Updated cabal-install test scripts to use the main Cabal repo.
> [EMAIL PROTECTED] 
> [Added cabal-install test scripts.
> [EMAIL PROTECTED] 
> [Added cabal-install Makefile.
> [EMAIL PROTECTED] 
> [Added HTTP package code used by cabal-install.
> [EMAIL PROTECTED] 
> [Imported all the cabal-install sources.
> [EMAIL PROTECTED] 
> [Added cabal-install dep on regex-compat.
> [EMAIL PROTECTED] 
> [Removed old CabalInstall.hs (it has moved to cabal-install/src in one of the 
> pataches I pulled in).
> [EMAIL PROTECTED] 
> [Pulling in cabal-install: changed default Hackage DB URL.
> [EMAIL PROTECTED] 
> [Pulling cabal-with-install into Cabal: cabal-install.cabal changes.
> [EMAIL PROTECTED] 
> [Pulling changes from cabal-with-install: Multiple repositories.
> [EMAIL PROTECTED]
>  Original patch:
>  Sat Sep  2 00:13:40 CEST 2006  Paolo Martini <[EMAIL PROTECTED]>
>    * Multiple repositories.
> ] 
> [Pulling changes from cabal-with-install: Stripping off the dependencies, 
> only HTTP left
> [EMAIL PROTECTED]
>  Original patch:
>  Sun Aug 20 19:01:03 CEST 2006  Paolo Martini <[EMAIL PROTECTED]>
>    * Stripping off the dependencies, only HTTP left
> ] 
> [Resolve Makefile conflict from importing Cabal-with-install patches.
> [EMAIL PROTECTED] 
> [a program to test download & install a bunch of cabal packages
> [EMAIL PROTECTED] 
> [added --inplace trick to cabal build so that cabal-install can build on 
> machines without cabal.
> [EMAIL PROTECTED] 
> [First attempt to make a new repository (url in the configuration)
> Paolo Martini <[EMAIL PROTECTED]>**20060820180342] 
> [Tarball index format support
> Paolo Martini <[EMAIL PROTECTED]>**20060816223509] 
> [Quieten a test
> Ian Lynagh <[EMAIL PROTECTED]>**20070110175223] 
> [Pass 0 verbosity on to GHC when building
> Ian Lynagh <[EMAIL PROTECTED]>**20070110174050] 
> [More verbosity tweaking
> Ian Lynagh <[EMAIL PROTECTED]>**20070110172956] 
> [Rejig verbosity levels a bit; 1 is now the default (was 0)
> Ian Lynagh <[EMAIL PROTECTED]>**20070110165149] 
> [Make system tweaks to avoid cabal thinking it isn't bootstrapped when 
> running the testsuite
> Ian Lynagh <[EMAIL PROTECTED]>**20070110162940] 
> [Typo
> Ian Lynagh <[EMAIL PROTECTED]>**20070110154617] 
> [Refer to the right variables
> Ian Lynagh <[EMAIL PROTECTED]>**20070110151326] 
> [Give unrecognised flags more clearly
> Ian Lynagh <[EMAIL PROTECTED]>**20070110144650] 
> [Beautify
> Ian Lynagh <[EMAIL PROTECTED]>**20070110143711] 
> [Retab
> Ian Lynagh <[EMAIL PROTECTED]>**20070110143103] 
> [Remove some chatter from the test scripts
> Ian Lynagh <[EMAIL PROTECTED]>**20070110142756] 
> [Eliminate more warnings
> Ian Lynagh <[EMAIL PROTECTED]>**20070110142114] 
> [More -Wall clean fixes
> Ian Lynagh <[EMAIL PROTECTED]>**20070110135838] 
> [Improve cleaning
> Ian Lynagh <[EMAIL PROTECTED]>**20070110134230] 
> [-Wall clean fixes
> Ian Lynagh <[EMAIL PROTECTED]>**20070110125523
>  
>  This patch is sponsored by Hac 07.
>  Have you hacked a lambda today?
> ] 
> [Fix non-fatal problem with 'setup haddock' for an exe package
> Simon Marlow <[EMAIL PROTECTED]>**20070109133751
>  For some unknown reason, we were passing --use-package=P to haddock,
>  where P is the name of the current executable package.  This can never
>  work, since P is not a library and will not be installed.  Fortunately
>  Haddock ignores the error and continues anyway.
>  
> ] 
> [Set the Cabal version when building via the fptools build system
> [EMAIL PROTECTED]
>  
>  Without this patch, Cabal is effectively "version-less" and all .cabal
>  files with a version requirement are unusable. Therefore I think that
>  this patch (or at least something equivalent) should be pushed to the
>  6.6.1 branch, too.
> ] 
> [added --save-configure flag to clean. got some complaints that there was no 
> way to avoid reconfiguring after a clean.  now if you use --save-configure, 
> you should be able to.
> [EMAIL PROTECTED] 
> [tiny mod to License comments
> [EMAIL PROTECTED] 
> [improving help output
> [EMAIL PROTECTED]
>  As suggested by Claus Reinke in this ticket:
>  http://hackage.haskell.org/trac/hackage/ticket/105
> ] 
> [fix ./Setup unregister --help, which was giving the help for register
> Simon Marlow <[EMAIL PROTECTED]>**20061215165000] 
> [Fix the links in the user guide to the API docs
> Duncan Coutts <[EMAIL PROTECTED]>*-20061129131633] 
> [Fix the links in the user guide to the API docs
> Duncan Coutts <[EMAIL PROTECTED]>**20061129131633] 
> [haddock comments for SrcDist.hs
> [EMAIL PROTECTED] 
> [some haddock comments for LocalBuildInfo.hs
> [EMAIL PROTECTED] 
> [a little comment for JHC.hs
> [EMAIL PROTECTED] 
> [some comments for Install.hs
> [EMAIL PROTECTED] 
> [some comments for Hugs.hs
> [EMAIL PROTECTED] 
> [haddock comments for GHC and GHCPackageConig
> [EMAIL PROTECTED] 
> [some comments for Configure.hs
> [EMAIL PROTECTED] 
> [some comments for Build.hs
> [EMAIL PROTECTED] 
> [minor comments and cleanup for Setup.hs
> [EMAIL PROTECTED] 
> [some haddock explanation of preprocessors
> [EMAIL PROTECTED] 
> [some comments for Package.hs
> [EMAIL PROTECTED] 
> [haddockizing some comments from Make.hs
> [EMAIL PROTECTED] 
> [adding comments to Program.hs
> [EMAIL PROTECTED] 
> [comments for the Program module
> [EMAIL PROTECTED] 
> [don't return an error code just because there's no library to register
> [EMAIL PROTECTED] 
> [Purely cosmetic; have '--<FOO>-args' use ARGS on their RHS rather than PATH 
> in usage output
> [EMAIL PROTECTED] 
> [parse executable field as a token (as documented), rather than free text
> Ross Paterson <[EMAIL PROTECTED]>**20061120093400] 
> [trim trailing spaces (including CRs) from all input lines
> Ross Paterson <[EMAIL PROTECTED]>**20061120092526] 
> [help nhc98 find the import of programLocation
> [EMAIL PROTECTED] 
> [sdist: make it work on Windows platforms by simplifying 'tar' invocation. 
> Hopefully not at the cost of other plats (i.e., as-yet untested there..)"
> [EMAIL PROTECTED] 
> [build: consult and use any user-provided settings for 'ld' and 'ar'
> [EMAIL PROTECTED] 
> [defaultUserHooks.sDistHook: pass in optional LBI to SrcDist.sdist
> [EMAIL PROTECTED] 
> [defaultProgramConfiguration: add 'ld' and 'tar' entries
> [EMAIL PROTECTED] 
> [revise Paths module for the Hugs target
> Ross Paterson <[EMAIL PROTECTED]>**20061108223349
>  
>  When targetting Hugs, the Paths module now uses prefix-independent
>  paths relative to the location of the Main module of the program,
>  on all platforms.
>  
>  For the Hugs target, this replaces the code using GetModuleFileNameA(),
>  which never worked.  Behaviour under GHC should be unchanged.
> ] 
> [Hugs: fix location of installed package info
> Ross Paterson <[EMAIL PROTECTED]>**20061021144613] 
> [Fix escaping of ' chars in register.sh script.
> Duncan Coutts <[EMAIL PROTECTED]>**20061016215459] 
> [Tidy up command comments
> Duncan Coutts <[EMAIL PROTECTED]>**20061013211158] 
> [Fix getDataDir etc. when bindir=$prefix
> Simon Marlow <[EMAIL PROTECTED]>**20061013100941] 
> [Update text on the front page: packages can now overlap in GHC 6.6
> Simon Marlow <[EMAIL PROTECTED]>**20061012114601
>  
> ] 
> [New unlit code "ported" from cpphs-1.2
> Lennart Kolmodin <[EMAIL PROTECTED]>**20061009192609] 
> [Share one more place where the cabal version is defined.
> Duncan Coutts <[EMAIL PROTECTED]>**20061010140027] 
> [Fix spelling error in error message.
> Duncan Coutts <[EMAIL PROTECTED]>**20061010140013] 
> [Centeralise the places that know that Cabal version number
> Duncan Coutts <[EMAIL PROTECTED]>**20061010135918] 
> [Remove spurious debug message.
> Duncan Coutts <[EMAIL PROTECTED]>**20061010125643] 
> [Bump to next unstable development version
> Duncan Coutts <[EMAIL PROTECTED]>**20061010125602] 
> [Make cabal know it's own version number correctly
> Duncan Coutts <[EMAIL PROTECTED]>**20061010130939
>  This is an unpleasent way of doing it.
>  Will have to fix once and for all in the next version.
> ] 
> [TAG 1.1.6
> Duncan Coutts <[EMAIL PROTECTED]>**20061009123801] 
> Patch bundle hash:
> 343e137602e63baf88fb7c8cd0c5feac7c76d623
> _______________________________________________
> cabal-devel mailing list
> cabal-devel@haskell.org
> http://www.haskell.org/mailman/listinfo/cabal-devel

_______________________________________________
cabal-devel mailing list
cabal-devel@haskell.org
http://www.haskell.org/mailman/listinfo/cabal-devel

Reply via email to