On Fri, Nov 30, 2012 at 09:38:10AM -0800, Johan Tibell wrote:
> On Fri, Nov 30, 2012 at 9:11 AM, Simon Peyton-Jones
> <simo...@microsoft.com> wrote:
> > If Bryan and Johan are the Performance Tsars the future looks bright.  Or at
> > least fast.  Thank you.
> 
> If someone could point me to the build bot script that we run today
> that would be a great start.

The code is at http://darcs.haskell.org/builder/

The config, including the build steps, is attached.


Thanks
Ian

module Config (config) where

import Builder.BuildSteps
import Builder.Config
import Builder.Utils

import Data.Maybe

config :: Config
config = Config {
             config_fromAddress = fromAddress,
             config_emailAddresses = emailAddresses,
             config_urlRoot = urlRoot,
             config_clients = clients
         }

fromAddress :: String
fromAddress = "bit.buc...@galois.com"

emailAddresses :: [String]
emailAddresses = ["cvs-...@haskell.org"]

urlRoot :: String
urlRoot = "http://darcs.haskell.org/ghcBuilder/";

clients :: [(String, UserInfo)]
clients = []

stable :: BuildTime -> BuildTime
-- stable _ = NoBuilds
stable bt = bt

data Branch = Head | Stable

data GhcBuildConfig = GhcBuildConfig {
                          gbc_branch :: Branch,
                          gbc_repo :: Maybe String,
                          gbc_extraGitFlags :: [String],
                          gbc_iscc :: Maybe String,
                          gbc_installExtraPackages :: Maybe Bool,
                          gbc_haddockDocs :: Maybe Bool,
                          gbc_latexDocs :: Maybe Bool,
                          gbc_hscolourSources :: Maybe Bool,
                          gbc_docbookHtml :: Maybe Bool,
                          gbc_docbookPdf :: Maybe Bool,
                          gbc_docbookPs :: Maybe Bool,
                          gbc_bootInterpreter :: String,
                          gbc_makeCommand :: Maybe String,
                          gbc_mainMakeFlags :: [String],
                          gbc_configureFlags :: [String],
                          gbc_unregisterised :: Bool,
                          gbc_fullTestsuite :: Bool,
                          gbc_publishResults :: Maybe (String, -- command to publish
                                                       String, -- location to publish to
                                                       Bool)   -- publish docs too?
                      }

basicConfig :: GhcBuildConfig
basicConfig = GhcBuildConfig {
                  gbc_branch = Head,
                  gbc_repo = Nothing,
                  gbc_extraGitFlags = [],
                  gbc_iscc = Nothing,
                  gbc_installExtraPackages = Nothing,
                  gbc_haddockDocs = Nothing,
                  gbc_latexDocs = Nothing,
                  gbc_hscolourSources = Nothing,
                  gbc_docbookHtml = Nothing,
                  gbc_docbookPdf = Nothing,
                  gbc_docbookPs = Nothing,
                  gbc_bootInterpreter = "perl",
                  gbc_makeCommand = Nothing,
                  gbc_mainMakeFlags = [],
                  gbc_configureFlags = [],
                  gbc_unregisterised = False,
                  gbc_fullTestsuite = False,
                  gbc_publishResults = Nothing
              }

headConfig :: GhcBuildConfig
headConfig = basicConfig {
                 gbc_installExtraPackages = Just True
             }

stableConfig :: GhcBuildConfig
stableConfig = basicConfig {
                   gbc_branch = Stable
               }

completeBuild :: GhcBuildConfig -> GhcBuildConfig
completeBuild c = c {
                      gbc_haddockDocs = Just True,
                      gbc_latexDocs = Just True,
                      gbc_hscolourSources = Just True,
                      gbc_docbookHtml = Just True,
                      gbc_docbookPdf = Just True,
                      gbc_docbookPs = Just True
                  }

ghcBuildSteps :: GhcBuildConfig -> [BuildStep]
ghcBuildSteps gbc =
    [BuildStep {
         bs_name = "git clone",
         bs_subdir = ".",
         bs_mailOutput = False,
         bs_prog = "git",
         bs_args = let gitRepo = case gbc_repo gbc of
                                 Just r -> r
                                 Nothing ->
                                     "http://darcs.haskell.org/ghc.git/";
                   in ["clone"] ++ branchFlags ++ gbc_extraGitFlags gbc ++ [gitRepo, "build"]
     },
     BuildStep {
         bs_name = "create mk/build.mk",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = "sh",
         bs_args = let ls = ["V=1"]
                         ++ ["InstallExtraPackages=" ++ toYesNo b | Just b <- [gbc_installExtraPackages gbc]]
                         ++ ["HADDOCK_DOCS="         ++ toYesNo b | Just b <- [gbc_haddockDocs gbc]]
                         ++ ["LATEX_DOCS="           ++ toYesNo b | Just b <- [gbc_latexDocs gbc]]
                         ++ ["HSCOLOUR_SRCS="        ++ toYesNo b | Just b <- [gbc_hscolourSources gbc]]
                         ++ ["BUILD_DOCBOOK_HTML="   ++ toYesNo b | Just b <- [gbc_docbookHtml gbc]]
                         ++ ["BUILD_DOCBOOK_PDF="    ++ toYesNo b | Just b <- [gbc_docbookPdf gbc]]
                         ++ ["BUILD_DOCBOOK_PS="     ++ toYesNo b | Just b <- [gbc_docbookPs gbc]]
                         ++ ["ISCC_CMD="             ++ iscc      | Just iscc <- [gbc_iscc gbc]]
                         ++ ["PublishCp="            ++ c         | Just (c, _, _)   <- [gbc_publishResults gbc]]
                         ++ ["PublishLocation="      ++ loc       | Just (_, loc, _) <- [gbc_publishResults gbc]]
                         ++ ["BeConservative=YES"                 | isJust (gbc_publishResults gbc)]
                         ++ ["GhcUnregisterised=YES"              | gbc_unregisterised gbc]
                       str = concatMap (++ "\n") ls
                   in ["-c", "printf '" ++ str ++ "' | tee mk/build.mk"]
     },
     BuildStep {
         bs_name = "get subrepos",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = "perl",
         bs_args = ["./sync-all", "--testsuite", "get"] ++ branchFlags
     },
     BuildStep {
         bs_name = "repo versions",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = "perl",
         bs_args = ["./sync-all", "log", "HEAD^..", "--pretty=oneline"]
     },
     BuildStep {
         bs_name = "touching clean-check files",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = "touch",
         bs_args = ["check-remove-before",
                    "check-remove-after",
                    "would-be-cleaned"]
     },
     BuildStep {
         bs_name = "setting version date",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = "sh",
         bs_args = ["-c", "date +%Y%m%d | tee VERSION_DATE"]
     },
     BuildStep {
         bs_name = "booting",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = gbc_bootInterpreter gbc,
         bs_args = ["boot"]
     },
     BuildStep {
         bs_name = "configuring",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = "sh",
         bs_args = ["./configure"] ++ gbc_configureFlags gbc
     },
     BuildStep {
         bs_name = "creating check-remove-before",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = "sh",
         bs_args = ["-c", "find . > check-remove-before"]
     },
     BuildStep {
         bs_name = "compiling",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = fromMaybe "make" (gbc_makeCommand gbc),
         bs_args = gbc_mainMakeFlags gbc
     },
     BuildStep {
         bs_name = "creating check-remove-after",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = "sh",
         bs_args = ["-c", "find . > check-remove-after"]
     },
     BuildStep {
         bs_name = "compiling testremove",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = fromMaybe "make" (gbc_makeCommand gbc),
         bs_args = ["utils/testremove_all"]
     },
     BuildStep {
         bs_name = "simulating clean",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = fromMaybe "make" (gbc_makeCommand gbc),
         bs_args = ["clean", "ONLY_SHOW_CLEANS=YES"]
     },
     BuildStep {
         bs_name = "checking clean",
         bs_subdir = "build",
         bs_mailOutput = True,
         bs_prog = "utils/testremove/checkremove",
         bs_args = ["check-remove-before",
                    "check-remove-after",
                    "would-be-cleaned"]
     },
     BuildStep {
         bs_name = "making bindist",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = fromMaybe "make" (gbc_makeCommand gbc),
         bs_args = ["binary-dist"]
     }]
 ++ [BuildStep {
         bs_name = "publishing bindist",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = fromMaybe "make" (gbc_makeCommand gbc),
         bs_args = ["publish-binary-dist"]
     }
    | isJust (gbc_publishResults gbc)]
 ++ [BuildStep {
         bs_name = "testing bindist",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = fromMaybe "make" (gbc_makeCommand gbc),
         bs_args = ["test_bindist"]
     }]
 ++ [BuildStep {
         bs_name = "publishing docs",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = fromMaybe "make" (gbc_makeCommand gbc),
         bs_args = ["publish-docs"]
     }
    | Just (_, _, True) <- [gbc_publishResults gbc]]
 ++ [
     let target = if gbc_fullTestsuite gbc then "fulltest" else "test" in
     BuildStep {
         bs_name = "testing",
         bs_subdir = "build",
         bs_mailOutput = False,
         bs_prog = fromMaybe "make" (gbc_makeCommand gbc),
         bs_args = [target, "BINDIST=YES"]
     },
     BuildStep {
         bs_name = "testsuite summary",
         bs_subdir = "build",
         bs_mailOutput = True,
         bs_prog = "cat",
         bs_args = ["testsuite_summary.txt"]
     }
     ]
    where branchFlags = case gbc_branch gbc of
                        Head -> []
                        Stable -> ["-b", "ghc-7.6"]

toYesNo :: Bool -> String
toYesNo True = "YES"
toYesNo False = "NO"

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to