[commit: ghc] wip/nfs-locking: Add GhcSplit and Unlit builders. (47c7ab1)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:08:23 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/nfs-locking
Link       : http://ghc.haskell.org/trac/ghc/changeset/47c7ab173f636eb0c636765b412c523bdb3e7fb3/ghc

>---------------------------------------------------------------

commit 47c7ab173f636eb0c636765b412c523bdb3e7fb3
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Thu Sep 24 05:43:05 2015 +0100

    Add GhcSplit and Unlit builders.


>---------------------------------------------------------------

47c7ab173f636eb0c636765b412c523bdb3e7fb3
 cfg/system.config.in |  4 ++++
 src/Builder.hs       | 11 ++++++++++-
 2 files changed, 14 insertions(+), 1 deletion(-)

diff --git a/cfg/system.config.in b/cfg/system.config.in
index 2bfe449..87d2b93 100644
--- a/cfg/system.config.in
+++ b/cfg/system.config.in
@@ -23,6 +23,9 @@ hsc2hs         = @hardtop@/inplace/bin/hsc2hs
 
 genprimopcode  = @hardtop@/inplace/bin/genprimopcode
 
+unlit          = @hardtop@/inplace/lib/unlit
+ghc-split      = @hardtop@/inplace/lib/ghc-split
+
 ld             = @LdCmd@
 ar             = @ArCmd@
 alex           = @AlexCmd@
@@ -43,6 +46,7 @@ solaris-broken-shld  = @SOLARIS_BROKEN_SHLD@
 split-objects-broken = @SplitObjsBroken@
 ghc-unregisterised   = @Unregisterised@
 ghc-source-path      = @hardtop@
+leading-underscore   = @LeadingUnderscore@
 
 # Information about host and target systems:
 #===========================================
diff --git a/src/Builder.hs b/src/Builder.hs
index 9448ed2..a6521a1 100644
--- a/src/Builder.hs
+++ b/src/Builder.hs
@@ -1,5 +1,7 @@
 {-# LANGUAGE DeriveGeneric #-}
-module Builder (Builder (..), builderPath, specified, needBuilder) where
+module Builder (
+    Builder (..), builderPath, getBuilderPath, specified, needBuilder
+    ) where
 
 import Base
 import GHC.Generics (Generic)
@@ -24,11 +26,13 @@ data Builder = Alex
              | GhcCabalHsColour
              | GhcM Stage
              | GhcPkg Stage
+             | GhcSplit
              | Haddock
              | Happy
              | HsColour
              | Hsc2Hs
              | Ld
+             | Unlit
              deriving (Show, Eq, Generic)
 
 -- Configuration files refer to Builders as follows:
@@ -49,11 +53,13 @@ builderKey builder = case builder of
     GhcCabalHsColour -> builderKey $ GhcCabal -- synonym for 'GhcCabal hscolour'
     GhcPkg Stage0    -> "system-ghc-pkg"
     GhcPkg _         -> "ghc-pkg"
+    GhcSplit         -> "ghc-split"
     Happy            -> "happy"
     Haddock          -> "haddock"
     HsColour         -> "hscolour"
     Hsc2Hs           -> "hsc2hs"
     Ld               -> "ld"
+    Unlit            -> "unlit"
 
 builderPath :: Builder -> Action FilePath
 builderPath builder = do
@@ -62,6 +68,9 @@ builderPath builder = do
                      ++ "' in configuration files."
     fixAbsolutePathOnWindows $ if null path then "" else path -<.> exe
 
+getBuilderPath :: Builder -> ReaderT a Action FilePath
+getBuilderPath = lift . builderPath
+
 specified :: Builder -> Action Bool
 specified = fmap (not . null) . builderPath
 



More information about the ghc-commits mailing list