cabal-setup

Simon Marlow simonmarhaskell at gmail.com
Fri Mar 3 12:16:51 EST 2006


Lemmih wrote:

> Did you forget to attach the patch or am I looking in the wrong places?

oops.  attached.

-------------- next part --------------

New patches:

[First attempt at a cabal-setup command
Simon Marlow <simonmar at microsoft.com>**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 libraries at haskell.org.
] {
adddir ./cabal-setup
addfile ./cabal-setup/CabalSetup.hs
hunk ./cabal-setup/CabalSetup.hs 1
+{-# OPTIONS_GHC -cpp #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  CabalSetup
+-- Copyright   :  (c) The University of Glasgow 2006
+-- 
+-- Maintainer  :  http://hackage.haskell.org/trac/hackage
+-- Stability   :  alpha
+-- Portability :  portable
+--
+-- The user interface to building and installing Cabal packages.
+
+module Main (main) where
+
+import Distribution.Simple
+import Distribution.Simple.Utils
+import Distribution.Simple.Configure
+				( configCompiler, getInstalledPackages,
+		  	  	  configDependency )
+import Distribution.Setup	( reqPathArg )
+import Distribution.PackageDescription	 
+				( readPackageDescription,
+				  PackageDescription(..) )
+import System.Console.GetOpt
+import System.Environment
+import Control.Monad		( when )
+import System.Directory 	( doesFileExist )
+
+main = do
+  args <- getArgs
+  
+  -- read the .cabal file
+  -- 	- attempt to find the version of Cabal required
+
+  -- if there's a Setup script, 
+  --    - if we find GHC,
+  --	    - build it with the right version of Cabal
+  --        - invoke it with args
+  --    - if we find runhaskell (TODO)
+  --        - use runhaskell to invoke it
+  -- otherwise,
+  --	- behave like a boilerplate Setup.hs
+  --
+  -- Later:
+  --    - add support for multiple packages, by figuring out
+  --      dependencies here and building/installing the sub packages
+  --      in the right order.
+
+  pkg_descr_file <- defaultPackageDesc
+  pkg_descr <- readPackageDescription pkg_descr_file
+  
+  let (flag_fn, non_opts, unrec_opts, errs) = getOpt' Permute opts args
+  when (not (null errs)) $ die (unlines errs)
+  let flags = foldr (.) id flag_fn defaultFlags
+
+  comp <- configCompiler (Just GHC) (withCompiler flags) (withHcPkg flags) 0
+  cabal_flag <- configCabalFlag flags (descCabalVersion pkg_descr) comp
+
+  let
+    trySetupScript f on_fail = do
+       b <- doesFileExist f
+       if not b then on_fail else do
+       rawSystemExit (verbose flags)
+         (compilerPath comp)
+         (cabal_flag ++ 
+          ["--make", f, "-o", "setup", "-v"++show (verbose flags)])
+       rawSystemExit (verbose flags)
+         ('.':pathSeparator:"setup")
+         args
+
+  trySetupScript "Setup.hs"  $ do
+  trySetupScript "Setup.lhs" $ do
+  trySetupScript ".Setup.hs" $ do
+  
+  -- Setup.hs doesn't exist, we need to behave like defaultMain
+  if descCabalVersion pkg_descr == AnyVersion
+	then defaultMain
+		-- doesn't matter which version we use, so no need to compile
+		-- a special Setup.hs.
+	else do writeFile ".Setup.hs" 
+			  "import Distribution.Simple; main=defaultMain"
+		trySetupScript ".Setup.hs" $ error "panic! shouldn't happen"
+
+data Flags
+  = Flags {
+    withCompiler :: Maybe FilePath,
+    withHcPkg    :: Maybe FilePath,
+    verbose      :: Int
+  }
+
+defaultFlags = Flags {
+  withCompiler = Nothing,
+  withHcPkg    = Nothing,
+  verbose      = 0
+ }
+
+setWithCompiler f flags = flags{ withCompiler=f }
+setWithHcPkg    f flags = flags{ withHcPkg=f }
+setVerbose      v flags = flags{ verbose=v }
+
+opts :: [OptDescr (Flags -> Flags)]
+opts = [
+           Option "w" ["with-compiler"] (reqPathArg (setWithCompiler.Just))
+               "give the path to a particular compiler",
+           Option "" ["with-hc-pkg"] (reqPathArg (setWithHcPkg.Just))
+               "give the path to the package tool",
+	   Option "v" ["verbose"] (OptArg (setVerbose . maybe 3 read) "n") "Control verbosity (n is 0--5, normal verbosity level is 1, -v alone is equivalent to -v3)"
+  ]
+
+noSetupScript = error "noSetupScript"
+
+configCabalFlag :: Flags -> VersionRange -> Compiler -> IO [String]
+configCabalFlag flags AnyVersion _ = return []
+configCabalFlag flags range comp = do
+  ipkgs <-  getInstalledPackages comp True (verbose flags)
+	-- user packages are *allowed* here, no portability problem
+  cabal_pkgid <- configDependency ipkgs (Dependency "Cabal" range)
+  return ["-package", showPackageId cabal_pkgid]
+
+pathSeparator :: Char
+#if mingw32_HOST_OS || mingw32_TARGET_OS
+pathSeparator = '\\'
+#else
+pathSeparator = '/'
+#endif
addfile ./cabal-setup/Setup.hs
hunk ./cabal-setup/Setup.hs 1
+import Distribution.Simple; main=defaultMain
addfile ./cabal-setup/cabal-setup.cabal
hunk ./cabal-setup/cabal-setup.cabal 1
+Name: cabal-setup
+Version: 1.1.4
+Copyright: 2005, Simon Marlow
+Build-depends: Cabal >= 1.1.4, base
+License: BSD3
+License-File: ../LICENSE
+Author: Simon Marlow <simonmar at microsoft.com>
+Maintainer: http://hackage.haskell.org/trac/hackage/
+Homepage: http://www.haskell.org/cabal/
+Category: Distribution
+Synopsis: The user interface for building and installing Cabal packages
+Description:
+	cabal-setup is the user interface to Cabal.  It provides the
+ 	basic commands for configuring, building, and installing
+	Cabal packages.
+
+Executable: cabal-setup
+Main-is: CabalSetup.hs
}

Context:

[Support for -split-objs with GHC
Simon Marlow <simonmar at microsoft.com>**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 at cs.helsinki.fi>**20060206233543] 
[added some fields to test suite for duncan's mods
ijones at syntaxpolice.org**20060204223256] 
[fixup PackageDescription test code
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060201183912
 just ignore the extra ParseOk warnings field
] 
[ignore "x-" extension fields without a warning
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060201183145] 
[Make unknown fields a warning rather than an error
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**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 <simonmar at microsoft.com>**20060206095833] 
[push and pull all
ijones at syntaxpolice.org**20060201185441] 
[combine GNUmakefile and Makefile
Simon Marlow <simonmar at microsoft.com>**20060206095400] 
[now build Setup.lhs instead of using runghc on it. still uses runhugs.
ijones at syntaxpolice.org**20060130054810] 
[cabal-install uses defaultMain if it can't find Setup.lhs
ijones at syntaxpolice.org**20060130050710] 
[cleaned up suffix handler params to hooks
ijones at syntaxpolice.org**20060116064811
 
 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
ijones at syntaxpolice.org**20060116055858] 
[remove some flags from sdist, some cleanup
ijones at syntaxpolice.org**20060116053818] 
[clarifying and making flags types consistent
ijones at syntaxpolice.org**20060116035033] 
[changing tuple types to records w/ fields
ijones at syntaxpolice.org**20060115234317] 
[moving TODO stuff to wiki
ijones at syntaxpolice.org**20060115234303] 
[fix version number in fptools makefile to match .cabal file
ijones at syntaxpolice.org**20060201183331] 
[Add extraGHCiLibraries to the InstalledPackageInfo and extend the parser.
Duncan Coutts <duncan.coutts at worc.ox.ac.uk>**20060131163640] 
[re-add the GNUmakefiles
Simon Marlow <simonmar at microsoft.com>*-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 <simonmar at microsoft.com>**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
simonmar at microsoft.com**20060113152542] 
Patch bundle hash:
672bd0cb1499e7c9ca53a2a384ee9d0d8396bb86


More information about the Libraries mailing list