[commit: ghc] wip/nfs-locking: Build compact library (374b10a)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 01:15:22 UTC 2017


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

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

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

commit 374b10aa7af36884484e05d7e6ac02295be60957
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Sat Dec 31 01:04:40 2016 +0000

    Build compact library


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

374b10aa7af36884484e05d7e6ac02295be60957
 src/GHC.hs              | 33 ++++++++++++++++++---------------
 src/Settings/Default.hs |  3 ++-
 2 files changed, 20 insertions(+), 16 deletions(-)

diff --git a/src/GHC.hs b/src/GHC.hs
index 1fff56f..f8abeb8 100644
--- a/src/GHC.hs
+++ b/src/GHC.hs
@@ -1,13 +1,14 @@
 {-# LANGUAGE OverloadedStrings, LambdaCase #-}
 {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
 module GHC (
-    array, base, binary, bytestring, cabal, checkApiAnnotations, compiler,
-    containers, compareSizes, deepseq, deriveConstants, directory, dllSplit,
-    filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci,
-    ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hoopl, hp2ps,
-    hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart,
-    parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell,
-    terminfo, time, touchy, transformers, unlit, unix, win32, xhtml,
+    array, base, binary, bytestring, cabal, checkApiAnnotations, compact,
+    compareSizes, compiler, containers, deepseq, deriveConstants, directory,
+    dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh,
+    ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline,
+    hsc2hs, hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin,
+    libffi, mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc,
+    stm, templateHaskell, terminfo, time, touchy, transformers, unlit, unix,
+    win32, xhtml,
 
     defaultKnownPackages, builderProvenance, programName, nonCabalContext,
     nonHsMainPackage
@@ -25,13 +26,14 @@ import Stage
 -- be overridden in @hadrian/src/UserSettings.hs at .
 defaultKnownPackages :: [Package]
 defaultKnownPackages =
-    [ array, base, binary, bytestring, cabal, checkApiAnnotations, compiler
-    , containers, compareSizes, deepseq, deriveConstants, directory, dllSplit
-    , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghci
-    , ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hoopl, hp2ps, hpc
-    , hpcBin, integerGmp, integerSimple, iservBin, libffi, mkUserGuidePart
-    , parallel, pretty, primitive, process, rts, runGhc, stm, templateHaskell
-    , terminfo, time, touchy, transformers, unlit, unix, win32, xhtml ]
+    [ array, base, binary, bytestring, cabal, checkApiAnnotations, compact
+    , compareSizes, compiler, containers, deepseq, deriveConstants, directory
+    , dllSplit, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh
+    , ghcCabal, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs
+    , hoopl, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iservBin, libffi
+    , mkUserGuidePart, parallel, pretty, primitive, process, rts, runGhc, stm
+    , templateHaskell, terminfo, time, touchy, transformers, unlit, unix, win32
+    , xhtml ]
 
 -- | Package definitions, see 'Package'.
 array               = library  "array"
@@ -40,9 +42,10 @@ binary              = library  "binary"
 bytestring          = library  "bytestring"
 cabal               = library  "Cabal"        `setPath` "libraries/Cabal/Cabal"
 checkApiAnnotations = utility  "check-api-annotations"
+compact             = library  "compact"
+compareSizes        = utility  "compareSizes" `setPath` "utils/compare_sizes"
 compiler            = topLevel "ghc"          `setPath` "compiler"
 containers          = library  "containers"
-compareSizes        = utility  "compareSizes" `setPath` "utils/compare_sizes"
 deepseq             = library  "deepseq"
 deriveConstants     = utility  "deriveConstants"
 directory           = library  "directory"
diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs
index 37fcdfa..67b0d5d 100644
--- a/src/Settings/Default.hs
+++ b/src/Settings/Default.hs
@@ -90,8 +90,9 @@ stage1Packages = do
             , append $ [ array
                        , base
                        , bytestring
-                       , containers
+                       , compact
                        , compareSizes
+                       , containers
                        , deepseq
                        , directory
                        , filepath



More information about the ghc-commits mailing list