[commit: ghc] wip/nfs-locking: Rename compact to ghc-compact (30708a4)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:49:36 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/30708a47a3456f68bca6951232c02b26dda86585/ghc
>---------------------------------------------------------------
commit 30708a47a3456f68bca6951232c02b26dda86585
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Thu Mar 16 01:17:01 2017 +0000
Rename compact to ghc-compact
>---------------------------------------------------------------
30708a47a3456f68bca6951232c02b26dda86585
src/GHC.hs | 25 ++++++++++++-------------
src/Settings/Default.hs | 2 +-
2 files changed, 13 insertions(+), 14 deletions(-)
diff --git a/src/GHC.hs b/src/GHC.hs
index f8abeb8..33af662 100644
--- a/src/GHC.hs
+++ b/src/GHC.hs
@@ -1,14 +1,13 @@
{-# LANGUAGE OverloadedStrings, LambdaCase #-}
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
module GHC (
- 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,
+ array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes,
+ compiler, containers, deepseq, deriveConstants, directory, dllSplit, filepath,
+ genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, 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
@@ -26,10 +25,10 @@ import Stage
-- be overridden in @hadrian/src/UserSettings.hs at .
defaultKnownPackages :: [Package]
defaultKnownPackages =
- [ 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
+ [ array, base, binary, bytestring, cabal, checkApiAnnotations, compareSizes
+ , compiler, containers, deepseq, deriveConstants, directory, dllSplit
+ , filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal
+ , ghcCompact, 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
@@ -42,7 +41,6 @@ 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"
@@ -57,6 +55,7 @@ ghc = topLevel "ghc-bin" `setPath` "ghc" `setType` Progra
ghcBoot = library "ghc-boot"
ghcBootTh = library "ghc-boot-th"
ghcCabal = utility "ghc-cabal"
+ghcCompact = library "ghc-compact"
ghci = library "ghci"
ghcPkg = utility "ghc-pkg"
ghcPrim = library "ghc-prim"
diff --git a/src/Settings/Default.hs b/src/Settings/Default.hs
index 318b0a0..89db236 100644
--- a/src/Settings/Default.hs
+++ b/src/Settings/Default.hs
@@ -120,13 +120,13 @@ stage1Packages = do
, append $ [ array
, base
, bytestring
- , compact
, containers
, deepseq
, directory
, filepath
, ghc
, ghcCabal
+ , ghcCompact
, ghci
, ghcPrim
, haskeline
More information about the ghc-commits
mailing list