From cb7aa1ef2ec9671b0f38506fdf619577c8a052eb Mon Sep 17 00:00:00 2001
From: Ross Paterson <ross@soi.city.ac.uk>
Date: Thu, 11 Jan 2007 23:30:18 +0000
Subject: [PATCH] add a Build-Type field, and use it in setupWrapper

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.
---
 Distribution/PackageDescription.hs | 22 ++++++++++++--
 Distribution/ParseUtils.hs         |  6 +++-
 Distribution/SetupWrapper.hs       | 46 ++++++++++++++++++------------
 doc/Cabal.xml                      | 25 ++++++++++++++--
 4 files changed, 75 insertions(+), 24 deletions(-)

diff --git a/Distribution/PackageDescription.hs b/Distribution/PackageDescription.hs
index 36adf4b20c..917d1d9530 100644
--- a/Distribution/PackageDescription.hs
+++ b/Distribution/PackageDescription.hs
@@ -60,6 +60,7 @@ module Distribution.PackageDescription (
         Executable(..),
         withExe,
         exeModules,
+        BuildType(..),
         -- * Build information
         BuildInfo(..),
         emptyBuildInfo,
@@ -77,6 +78,7 @@ module Distribution.PackageDescription (
         hcOptions,
         autogenModuleName,
         haddockName,
+        cabalVersion,
 #ifdef DEBUG
         hunitTests,
         test
@@ -144,6 +146,7 @@ data PackageDescription
         category       :: String,
         buildDepends   :: [Dependency],
         descCabalVersion :: VersionRange, -- ^If this package depends on a specific version of Cabal, give that here.
+        buildType      :: BuildType,
         -- components
         library        :: Maybe Library,
         executables    :: [Executable],
@@ -168,6 +171,7 @@ emptyPackageDescription
                       license      = AllRightsReserved,
                       licenseFile  = "",
                       descCabalVersion = AnyVersion,
+                      buildType    = Custom,
                       copyright    = "",
                       maintainer   = "",
                       author       = "",
@@ -270,6 +274,16 @@ type HookedBuildInfo = (Maybe BuildInfo, [(String, BuildInfo)])
 emptyHookedBuildInfo :: HookedBuildInfo
 emptyHookedBuildInfo = (Nothing, [])
 
+-- | The type of build system used by this package.
+data BuildType
+  = Simple      -- ^ calls @Distribution.Simple.defaultMain@
+  | Configure   -- ^ calls @Distribution.Simple.defaultMainWithHooks defaultUserHooks@,
+                -- which invokes @configure@ to generate additional build
+                -- information used by later phases.
+  | Make        -- ^ calls @Distribution.Make.defaultMain@
+  | Custom      -- ^ uses user-supplied @Setup.hs@ or @Setup.lhs@ (default)
+                deriving (Show, Read, Eq)
+
 -- ------------------------------------------------------------
 -- * Utils
 -- ------------------------------------------------------------
@@ -381,6 +395,9 @@ basicStanzaFields =
  , simpleField "cabal-version"
                            (text . showVersionRange) parseVersionRange
                            descCabalVersion       (\v pkg -> pkg{descCabalVersion=v})
+ , simpleField "build-type"
+                           (text . show)          parseReadSQ
+                           buildType              (\t pkg -> pkg{buildType=t})
  , simpleField "license"
                            (text . show)          parseLicenseQ
                            license                (\l pkg -> pkg{license=l})
@@ -786,7 +803,8 @@ testPkgDescAnswer =
                     synopsis = "a nice package!",
                     description = "a really nice package!",
                     category = "tools",
-                               descCabalVersion=LaterVersion (Version [1,1,1] []),
+                    descCabalVersion=LaterVersion (Version [1,1,1] []),
+                    buildType=Custom,
                     buildDepends = [Dependency "haskell-src" AnyVersion,
                                      Dependency "HUnit"
                                      (UnionVersionRanges (ThisVersion (Version [1,0,0] ["rain"]))
@@ -883,7 +901,7 @@ comparePackageDescriptions :: PackageDescription
                            -> PackageDescription
                            -> [String]      -- ^Errors
 comparePackageDescriptions p1 p2
-    = catMaybes $ myCmp package "package" : myCmp license "license": myCmp licenseFile "licenseFile":  myCmp copyright "copyright":  myCmp maintainer "maintainer":  myCmp author "author":  myCmp stability "stability":  myCmp testedWith "testedWith":  myCmp homepage "homepage":  myCmp pkgUrl "pkgUrl":  myCmp synopsis "synopsis":  myCmp description "description":  myCmp category "category":  myCmp buildDepends "buildDepends":  myCmp library "library":  myCmp executables "executables": myCmp descCabalVersion "cabal-version":[]
+    = catMaybes $ myCmp package "package" : myCmp license "license": myCmp licenseFile "licenseFile":  myCmp copyright "copyright":  myCmp maintainer "maintainer":  myCmp author "author":  myCmp stability "stability":  myCmp testedWith "testedWith":  myCmp homepage "homepage":  myCmp pkgUrl "pkgUrl":  myCmp synopsis "synopsis":  myCmp description "description":  myCmp category "category":  myCmp buildDepends "buildDepends":  myCmp library "library":  myCmp executables "executables": myCmp descCabalVersion "cabal-version": myCmp buildType "build-type": []
 
 
       where myCmp :: (Eq a, Show a) => (PackageDescription -> a)
diff --git a/Distribution/ParseUtils.hs b/Distribution/ParseUtils.hs
index e53097d39d..ab13755ed2 100644
--- a/Distribution/ParseUtils.hs
+++ b/Distribution/ParseUtils.hs
@@ -54,7 +54,7 @@ module Distribution.ParseUtils (
 	parseTestedWithQ, parseLicenseQ, parseExtensionQ, parseCommaList, parseOptCommaList,
 	showFilePath, showToken, showTestedWith, showDependency, showFreeText,
 	simpleField, listField, commaListField, optsField, 
-	parseReadS, parseQuoted,
+	parseReadS, parseReadSQ, parseQuoted,
   ) where
 
 import Text.PrettyPrint.HughesPJ
@@ -271,6 +271,10 @@ parseLicenseQ = parseQuoted parseReadS <++ parseReadS
 parseExtensionQ :: ReadP r Extension
 parseExtensionQ = parseQuoted parseReadS <++ parseReadS
 
+-- | Parse something optionally wrapped in quotes.
+parseReadSQ :: Read a => ReadP r a
+parseReadSQ = parseQuoted parseReadS <++ parseReadS
+
 parseTokenQ :: ReadP r String
 parseTokenQ = parseReadS <++ munch1 (\x -> not (isSpace x) && x /= ',')
 
diff --git a/Distribution/SetupWrapper.hs b/Distribution/SetupWrapper.hs
index 79eb77d190..08c1cf0b53 100644
--- a/Distribution/SetupWrapper.hs
+++ b/Distribution/SetupWrapper.hs
@@ -9,11 +9,14 @@
 -- Portability :  portable
 --
 -- The user interface to building and installing Cabal packages.
--- This builds the setup script and runs it with the given arguments.
--- If there is no setup script, it calls 'defaultMain'.
+-- If the @Built-Type@ field is specified as something other than
+-- 'Custom', and the current version of Cabal is acceptable, this performs
+-- setup actions directly.  Otherwise it builds the setup script and
+-- runs it with the given arguments.
 
 module Distribution.SetupWrapper (setupWrapper) where
 
+import qualified Distribution.Make as Make
 import Distribution.Simple
 import Distribution.Simple.Utils
 import Distribution.Simple.Configure
@@ -22,7 +25,8 @@ import Distribution.Simple.Configure
 import Distribution.Setup	( reqPathArg )
 import Distribution.PackageDescription	 
 				( readPackageDescription,
-				  PackageDescription(..) )
+				  PackageDescription(..),
+                                  BuildType(..), cabalVersion )
 import System.Console.GetOpt
 import System.Directory
 import Control.Exception        ( finally )
@@ -32,14 +36,14 @@ import System.Directory 	( doesFileExist, getCurrentDirectory, setCurrentDirecto
   -- read the .cabal file
   -- 	- attempt to find the version of Cabal required
 
-  -- if there's a Setup script, 
+  -- if the Cabal file specifies the build type (not Custom),
+  --    - behave like a boilerplate Setup.hs of that type
+  -- otherwise,
   --    - if we find GHC,
-  --	    - build it with the right version of Cabal
+  --	    - build the Setup script 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
@@ -78,18 +82,24 @@ setupWrapper args mdir = inDir mdir $ do
          ('.':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"
+  case lookup (buildType pkg_descr) buildTypes of
+    Just (mainAction, mainText) ->
+      if withinRange cabalVersion (descCabalVersion pkg_descr)
+	then mainAction         -- current version is OK, so no need
+                                -- to compile a special Setup.hs.
+	else do writeFile ".Setup.hs" mainText
 		trySetupScript ".Setup.hs" $ error "panic! shouldn't happen"
+    Nothing ->
+      trySetupScript "Setup.hs"  $
+      trySetupScript "Setup.lhs" $
+      die "no special Build-Type, but lacks Setup.hs or Setup.lhs"
+
+buildTypes :: [(BuildType, (IO (), String))]
+buildTypes = [
+  (Simple, (defaultMain, "import Distribution.Simple; main=defaultMain")),
+  (Configure, (defaultMainWithHooks defaultUserHooks,
+    "import Distribution.Simple; main=defaultMainWithHooks defaultUserHooks")),
+  (Make, (Make.defaultMain, "import Distribution.Make; main=defaultMain"))]
 
 inDir :: Maybe FilePath -> IO () -> IO ()
 inDir Nothing m = m
diff --git a/doc/Cabal.xml b/doc/Cabal.xml
index fddcae4ecf..0ee88a0cf7 100644
--- a/doc/Cabal.xml
+++ b/doc/Cabal.xml
@@ -5,6 +5,7 @@
     <!ENTITY Make      '<ulink url="../libraries/Cabal/Distribution-Make.html">Distribution.Make</ulink>'>
     <!ENTITY License   '<ulink url="../libraries/Cabal/Distribution-License.html#t:License"><literal>License</literal></ulink>'>
     <!ENTITY Extension '<ulink url="../libraries/Cabal/Language-Haskell-Extension.html#t:Extension"><literal>Extension</literal></ulink>'>
+    <!ENTITY BuildType '<ulink url="../libraries/Cabal/Distribution-PackageDescription.html#t:BuildType"><literal>BuildType</literal></ulink>'>
     <!ENTITY Alex '<ulink url="http://www.haskell.org/alex/"><command>alex</command></ulink>'>
     <!ENTITY Autoconf '<ulink url="http://www.gnu.org/software/autoconf/"><command>autoconf</command></ulink>'>
     <!ENTITY C2hs '<ulink url="http://www.cse.unsw.edu.au/~chak/haskell/c2hs/"><command>c2hs</command></ulink>'>
@@ -129,6 +130,7 @@ License:        BSD3
 Author:         Dean Herington
 Homepage:       http://hunit.sourceforge.net/
 Category:       Testing
+Build-Type:     Simple
 Build-Depends:  base
 Synopsis:       Unit testing framework for Haskell
 Exposed-modules:
@@ -149,6 +151,7 @@ Version:        0.0
 License:        BSD3
 Author:         Angela Author
 Synopsis:       Small package with two programs
+Build-Type:     Simple
 Build-Depends:  HUnit
 
 Executable:     program1
@@ -170,6 +173,7 @@ Version:         0.0
 License:         BSD3
 Author:          Angela Author
 Synopsis:        Package with library and two programs
+Build-Type:      Simple
 Build-Depends:   HUnit
 Exposed-Modules: A, B, C
 
@@ -366,6 +370,20 @@ Other-Modules:   A, C, Utils</programlisting>
             </listitem>
           </varlistentry>
 
+          <varlistentry>
+            <term>
+              <literal>build-type:</literal> <replaceable>identifier</replaceable>
+            </term>
+            <listitem>
+              <para>The type of build used by this package.
+                Build types are the constructors of the &BuildType; type,
+                defaulting to <literal>Custom</literal>.
+                If this field is given a value other than
+                <literal>Custom</literal>, some tools will be able to
+                build the package without using the setup script.</para>
+            </listitem>
+          </varlistentry>
+
            <varlistentry>
             <term>
               <literal>license:</literal> <replaceable>identifier</replaceable>
@@ -915,9 +933,10 @@ Other-Modules:   A, C, Utils</programlisting>
 
       <para>For some packages, especially those interfacing with C
         libraries, implementation details and the build procedure depend
-        on the build environment.  The simple build infrastructure
-        can handle many such situations using a slightly longer
-        <filename>Setup.hs</filename>:</para>
+        on the build environment.  A variant of the simple build
+        infrastructure (the <literal>build-type</literal>
+        <literal>Configure</literal>) handles many such situations using
+        a slightly longer <filename>Setup.hs</filename>:</para>
       <programlisting>
 import Distribution.Simple
 main = defaultMainWithHooks defaultUserHooks</programlisting>
-- 
GitLab