[commit: ghc] wip/nfs-locking: Drop dll-split related arguments to ghc-cabal (8f5ad00)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:58:54 UTC 2017


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

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

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

commit 8f5ad00e81b98ab84708737d24d90457250e3873
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Wed Aug 30 10:47:16 2017 +0100

    Drop dll-split related arguments to ghc-cabal
    
    See #404


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

8f5ad00e81b98ab84708737d24d90457250e3873
 src/Settings/Builders/GhcCabal.hs | 173 --------------------------------------
 1 file changed, 173 deletions(-)

diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs
index 4fd598b..475cc65 100644
--- a/src/Settings/Builders/GhcCabal.hs
+++ b/src/Settings/Builders/GhcCabal.hs
@@ -18,7 +18,6 @@ ghcCabalBuilderArgs = builder GhcCabal ? do
     mconcat [ arg "configure"
             , arg =<< pkgPath <$> getPackage
             , arg $ top -/- path
-            , dll0Args
             , withStaged $ Ghc CompileHs
             , withStaged (GhcPkg Update)
             , bootPackageDatabaseArgs
@@ -127,175 +126,3 @@ with b = do
 withStaged :: (Stage -> Builder) -> Args
 withStaged sb = with . sb =<< getStage
 
--- This is a positional argument, hence:
--- * if it is empty, we need to emit one empty string argument;
--- * otherwise, we must collapse it into one space-separated string.
-dll0Args :: Args
-dll0Args = do
-    context  <- getContext
-    dll0     <- expr $ buildDll0 context
-    withGhci <- expr ghcWithInterpreter
-    arg . unwords . concat $ [ modules     | dll0             ]
-                          ++ [ ghciModules | dll0 && withGhci ] -- see #9552
-  where
-    modules = [ "Annotations"
-              , "ApiAnnotation"
-              , "Avail"
-              , "Bag"
-              , "BasicTypes"
-              , "Binary"
-              , "BooleanFormula"
-              , "BreakArray"
-              , "BufWrite"
-              , "Class"
-              , "CmdLineParser"
-              , "CmmType"
-              , "CoAxiom"
-              , "ConLike"
-              , "Coercion"
-              , "Config"
-              , "Constants"
-              , "CoreArity"
-              , "CoreFVs"
-              , "CoreSubst"
-              , "CoreSyn"
-              , "CoreTidy"
-              , "CoreUnfold"
-              , "CoreUtils"
-              , "CoreSeq"
-              , "CoreStats"
-              , "CostCentre"
-              , "Ctype"
-              , "DataCon"
-              , "Demand"
-              , "Digraph"
-              , "DriverPhases"
-              , "DynFlags"
-              , "Encoding"
-              , "ErrUtils"
-              , "Exception"
-              , "ExtsCompat46"
-              , "FamInstEnv"
-              , "FastFunctions"
-              , "FastMutInt"
-              , "FastString"
-              , "FastTypes"
-              , "Fingerprint"
-              , "FiniteMap"
-              , "ForeignCall"
-              , "Hooks"
-              , "HsBinds"
-              , "HsDecls"
-              , "HsDoc"
-              , "HsExpr"
-              , "HsImpExp"
-              , "HsLit"
-              , "PlaceHolder"
-              , "HsPat"
-              , "HsSyn"
-              , "HsTypes"
-              , "HsUtils"
-              , "HscTypes"
-              , "IOEnv"
-              , "Id"
-              , "IdInfo"
-              , "IfaceSyn"
-              , "IfaceType"
-              , "InstEnv"
-              , "Kind"
-              , "Lexeme"
-              , "Lexer"
-              , "ListSetOps"
-              , "Literal"
-              , "Maybes"
-              , "MkCore"
-              , "MkId"
-              , "Module"
-              , "MonadUtils"
-              , "Name"
-              , "NameEnv"
-              , "NameSet"
-              , "OccName"
-              , "OccurAnal"
-              , "OptCoercion"
-              , "OrdList"
-              , "Outputable"
-              , "PackageConfig"
-              , "Packages"
-              , "Pair"
-              , "Panic"
-              , "PatSyn"
-              , "PipelineMonad"
-              , "Platform"
-              , "PlatformConstants"
-              , "PprCore"
-              , "PrelNames"
-              , "PrelRules"
-              , "Pretty"
-              , "PrimOp"
-              , "RdrName"
-              , "Rules"
-              , "Serialized"
-              , "SrcLoc"
-              , "StaticFlags"
-              , "StringBuffer"
-              , "TcEvidence"
-              , "TcRnTypes"
-              , "TcType"
-              , "TrieMap"
-              , "TyCon"
-              , "Type"
-              , "TypeRep"
-              , "TysPrim"
-              , "TysWiredIn"
-              , "Unify"
-              , "UniqFM"
-              , "UniqSet"
-              , "UniqSupply"
-              , "Unique"
-              , "Util"
-              , "Var"
-              , "VarEnv"
-              , "VarSet" ]
-    ghciModules = [ "Bitmap"
-                  , "BlockId"
-                  , "ByteCodeAsm"
-                  , "ByteCodeInstr"
-                  , "ByteCodeItbls"
-                  , "CLabel"
-                  , "Cmm"
-                  , "CmmCallConv"
-                  , "CmmExpr"
-                  , "CmmInfo"
-                  , "CmmMachOp"
-                  , "CmmNode"
-                  , "CmmSwitch"
-                  , "CmmUtils"
-                  , "CodeGen.Platform"
-                  , "CodeGen.Platform.ARM"
-                  , "CodeGen.Platform.ARM64"
-                  , "CodeGen.Platform.NoRegs"
-                  , "CodeGen.Platform.PPC"
-                  , "CodeGen.Platform.PPC_Darwin"
-                  , "CodeGen.Platform.SPARC"
-                  , "CodeGen.Platform.X86"
-                  , "CodeGen.Platform.X86_64"
-                  , "FastBool"
-                  , "InteractiveEvalTypes"
-                  , "MkGraph"
-                  , "PprCmm"
-                  , "PprCmmDecl"
-                  , "PprCmmExpr"
-                  , "Reg"
-                  , "RegClass"
-                  , "SMRep"
-                  , "StgCmmArgRep"
-                  , "StgCmmClosure"
-                  , "StgCmmEnv"
-                  , "StgCmmLayout"
-                  , "StgCmmMonad"
-                  , "StgCmmProf"
-                  , "StgCmmTicky"
-                  , "StgCmmUtils"
-                  , "StgSyn"
-                  , "Stream" ]



More information about the ghc-commits mailing list