Skip to content
Snippets Groups Projects
Unverified Commit 438dc576 authored by Andrey Mokhov's avatar Andrey Mokhov Committed by GitHub
Browse files

Finalise warnings-related arguments (#448)

* Fix non-exhaustive pattern match warning

* Move warnings-related settings to a separate module

* Move defaultHsWarningsArgs to Settings.Warnings, add -Wcpp-undef

* Use defaultGhcWarningsArgs in Settings.Builders.Ghc. Add -Wnoncanonical-monad-instances.

* Add warnings for ghc-cabal

* Add RTS warning flags

* Fix build with integer-simple library

* There are no tabs in xhtml
parent 4fd94c3f
No related merge requests found
......@@ -33,6 +33,7 @@ ar-supports-at-file = @ArSupportsAtFile@
cc-clang-backend = @CC_CLANG_BACKEND@
cc-llvm-backend = @CC_LLVM_BACKEND@
gcc-is-clang = @GccIsClang@
gcc-lt-34 = @GccLT34@
gcc-lt-44 = @GccLT44@
gcc-lt-46 = @GccLT46@
hs-cpp-args = @HaskellCPPArgs@
......
......@@ -99,6 +99,7 @@ executable hadrian
, Settings.Packages.IntegerGmp
, Settings.Packages.Rts
, Settings.Packages.RunGhc
, Settings.Warnings
, Stage
, Target
, UserSettings
......
......@@ -11,6 +11,7 @@ import Oracles.Setting
data Flag = ArSupportsAtFile
| CrossCompiling
| GccIsClang
| GccLt34
| GccLt44
| GccLt46
| GhcUnregisterised
......@@ -29,6 +30,7 @@ flag f = do
ArSupportsAtFile -> "ar-supports-at-file"
CrossCompiling -> "cross-compiling"
GccIsClang -> "gcc-is-clang"
GccLt34 -> "gcc-lt-34"
GccLt44 -> "gcc-lt-44"
GccLt46 -> "gcc-lt-46"
GhcUnregisterised -> "ghc-unregisterised"
......
......@@ -18,7 +18,7 @@ compilePackage rs context@Context {..} = do
need [src]
needDependencies context src $ obj <.> "d"
buildWithResources rs $ target context (compiler stage) [src] [obj]
compileHs [obj, _hi] = do
compileHs = \[obj, _hi] -> do
path <- buildPath context
(src, deps) <- lookupDependencies (path -/- ".dependencies") obj
need $ src : deps
......
......@@ -58,14 +58,14 @@ compilerDependencies :: Expr [FilePath]
compilerDependencies = do
root <- getBuildRoot
stage <- getStage
intLib <- expr (integerLibrary =<< flavour)
isGmp <- (== integerGmp) <$> getIntegerPackage
ghcPath <- expr $ buildPath (vanillaContext stage compiler)
gmpPath <- expr gmpBuildPath
rtsPath <- expr rtsBuildPath
mconcat [ return [root -/- platformH stage]
, return ((root -/-) <$> includesDependencies)
, return ((root -/-) <$> derivedConstantsDependencies)
, notStage0 ? intLib == integerGmp ? return [gmpPath -/- gmpLibraryH]
, notStage0 ? isGmp ? return [gmpPath -/- gmpLibraryH]
, notStage0 ? return ((rtsPath -/-) <$> libffiDependencies)
, return $ fmap (ghcPath -/-)
[ "primop-can-fail.hs-incl"
......@@ -270,7 +270,7 @@ generateConfigHs = do
cProjectPatchLevel1 <- getSetting ProjectPatchLevel1
cProjectPatchLevel2 <- getSetting ProjectPatchLevel2
cBooterVersion <- getSetting GhcVersion
intLib <- expr (integerLibrary =<< flavour)
intLib <- getIntegerPackage
debugged <- ghcDebugged <$> expr flavour
let cIntegerLibraryType
| intLib == integerGmp = "IntegerGMP"
......
module Settings (
getArgs, getLibraryWays, getRtsWays, flavour, knownPackages,
findPackageByName, getPkgData, getPkgDataList, isLibrary, stagePackages,
programContext, integerLibraryName, getDestDir
programContext, getIntegerPackage, getDestDir
) where
import CommandLine
......@@ -43,8 +43,8 @@ flavour = do
flavours = hadrianFlavours ++ userFlavours
return $ fromMaybe unknownFlavour $ find ((== flavourName) . name) flavours
integerLibraryName :: Action String
integerLibraryName = pkgName <$> (integerLibrary =<< flavour)
getIntegerPackage :: Expr Package
getIntegerPackage = expr (integerLibrary =<< flavour)
programContext :: Stage -> Package -> Action Context
programContext stage pkg = do
......
......@@ -11,10 +11,8 @@ ccBuilderArgs = do
, cIncludeArgs
, builder (Cc CompileC) ? mconcat
[ arg "-Werror"
[ pure ["-Wall", "-Werror"]
, Dynamic `wayUnit` way ? pure [ "-fPIC", "-DDYNAMIC" ]
-- ref: mk/warning.mk:
-- SRC_CC_OPTS += -Wall $(WERROR)
, arg "-c", arg =<< getInput
, arg "-o", arg =<< getOutput ]
......
module Settings.Builders.Ghc (
ghcBuilderArgs, ghcCBuilderArgs, ghcMBuilderArgs, haddockGhcArgs
) where
module Settings.Builders.Ghc (ghcBuilderArgs, haddockGhcArgs) where
import Hadrian.Haskell.Cabal
import Flavour
import Rules.Gmp
import Settings.Builders.Common
import Settings.Warnings
ghcBuilderArgs :: Args
ghcBuilderArgs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do
ghcBuilderArgs = mconcat [compileAndLinkHs, compileC, findHsDependencies]
compileAndLinkHs :: Args
compileAndLinkHs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do
needTouchy
mconcat [ arg "-Wall"
, commonGhcArgs
, splitObjectsArgs
, ghcLinkArgs
, defaultGhcWarningsArgs
, builder (Ghc CompileHs) ? arg "-c"
, getInputs
, arg "-o", arg =<< getOutput ]
......@@ -24,19 +27,18 @@ needTouchy = notStage0 ? windowsHost ? do
touchyPath <- expr $ programPath (vanillaContext Stage0 touchy)
expr $ need [touchyPath]
ghcCBuilderArgs :: Args
ghcCBuilderArgs = builder (Ghc CompileCWithGhc) ? do
compileC :: Args
compileC = builder (Ghc CompileCWithGhc) ? do
way <- getWay
let ccArgs = [ getPkgDataList CcArgs
, getStagedSettingList ConfCcArgs
, cIncludeArgs
, arg "-Werror"
, Dynamic `wayUnit` way ? pure [ "-fPIC", "-DDYNAMIC" ] ]
mconcat [ arg "-Wall"
, ghcLinkArgs
, commonGhcArgs
, mconcat (map (map ("-optc" ++) <$>) ccArgs)
, defaultGhcWarningsArgs
, arg "-c"
, getInputs
, arg "-o"
......@@ -49,7 +51,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
pkg <- getPackage
libs <- getPkgDataList DepExtraLibs
libDirs <- getPkgDataList DepLibDirs
intLib <- expr (integerLibrary =<< flavour)
intLib <- getIntegerPackage
gmpLibs <- if stage > Stage0 && intLib == integerGmp
then do -- TODO: get this data more gracefully
let strip = fromMaybe "" . stripPrefix "extra-libraries: "
......@@ -69,8 +71,8 @@ splitObjectsArgs = splitObjects <$> flavour ? do
expr $ need [ghcSplitPath]
arg "-split-objs"
ghcMBuilderArgs :: Args
ghcMBuilderArgs = builder (Ghc FindHsDependencies) ? do
findHsDependencies :: Args
findHsDependencies = builder (Ghc FindHsDependencies) ? do
ways <- getLibraryWays
mconcat [ arg "-M"
, commonGhcArgs
......
......@@ -13,7 +13,6 @@ import Expression
import Flavour
import Oracles.Flag
import Oracles.PackageData
import Oracles.Setting
import Settings
import Settings.Builders.Alex
import Settings.Builders.DeriveConstants
......@@ -43,6 +42,7 @@ import Settings.Packages.Haskeline
import Settings.Packages.IntegerGmp
import Settings.Packages.Rts
import Settings.Packages.RunGhc
import Settings.Warnings
-- TODO: Move C source arguments here
-- | Default and package-specific source arguments.
......@@ -68,23 +68,12 @@ defaultArgs = mconcat
, sourceArgs defaultSourceArgs
, defaultPackageArgs ]
-- ref: mk/warnings.mk
-- | Default Haskell warning-related arguments.
defaultHsWarningsArgs :: Args
defaultHsWarningsArgs = mconcat
[ notStage0 ? arg "-Werror"
, (not <$> flag GccIsClang) ? mconcat
[ (not <$> flag GccLt46) ? (not <$> windowsHost) ? arg "-optc-Werror=unused-but-set-variable"
, (not <$> flag GccLt44) ? arg "-optc-Wno-error=inline" ]
, flag GccIsClang ? arg "-optc-Wno-unknown-pragmas" ]
-- | Default source arguments, e.g. optimisation settings.
defaultSourceArgs :: SourceArgs
defaultSourceArgs = SourceArgs
{ hsDefault = mconcat [ stage0 ? arg "-O"
, notStage0 ? arg "-O2"
, arg "-H32m"
, defaultHsWarningsArgs ]
, arg "-H32m" ]
, hsLibrary = mempty
, hsCompiler = mempty
, hsGhc = mempty }
......@@ -148,8 +137,6 @@ defaultBuilderArgs = mconcat
, genPrimopCodeBuilderArgs
, ghcBuilderArgs
, ghcCabalBuilderArgs
, ghcCBuilderArgs
, ghcMBuilderArgs
, ghcPkgBuilderArgs
, haddockBuilderArgs
, happyBuilderArgs
......@@ -167,57 +154,20 @@ defaultBuilderArgs = mconcat
, builder (Tar Create ) ? Hadrian.Builder.Tar.args Create
, builder (Tar Extract ) ? Hadrian.Builder.Tar.args Extract ]
-- TODO: Disable warnings for Windows specifics.
-- TODO: Move this elsewhere?
-- ref: mk/warnings.mk
-- | Disable warnings in packages we use.
disableWarningArgs :: Args
disableWarningArgs = builder Ghc ? mconcat
[ stage0 ? mconcat
[ package terminfo ? pure [ "-fno-warn-unused-imports" ]
, package transformers ? pure [ "-fno-warn-unused-matches"
, "-fno-warn-unused-imports" ]
, libraryPackage ? pure [ "-fno-warn-deprecated-flags" ] ]
, notStage0 ? mconcat
[ package base ? pure [ "-Wno-trustworthy-safe" ]
, package binary ? pure [ "-Wno-deprecations" ]
, package bytestring ? pure [ "-Wno-inline-rule-shadowing" ]
, package directory ? pure [ "-Wno-unused-imports" ]
, package ghcPrim ? pure [ "-Wno-trustworthy-safe" ]
, package haddock ? pure [ "-Wno-unused-imports"
, "-Wno-deprecations" ]
, package haskeline ? pure [ "-Wno-deprecations"
, "-Wno-unused-imports"
, "-Wno-redundant-constraints"
, "-Wno-simplifiable-class-constraints" ]
, package pretty ? pure [ "-Wno-unused-imports" ]
, package primitive ? pure [ "-Wno-unused-imports"
, "-Wno-deprecations" ]
, package terminfo ? pure [ "-Wno-unused-imports" ]
, package transformers ? pure [ "-Wno-unused-matches"
, "-Wno-unused-imports"
, "-Wno-redundant-constraints"
, "-Wno-orphans" ]
, package win32 ? pure [ "-Wno-trustworthy-safe" ]
, package xhtml ? pure [ "-Wno-unused-imports"
, "-Wno-tabs" ]
, libraryPackage ? pure [ "-Wno-deprecated-flags" ] ] ]
-- | All 'Package'-dependent command line arguments.
defaultPackageArgs :: Args
defaultPackageArgs = mconcat
[ basePackageArgs
, cabalPackageArgs
, compilerPackageArgs
, ghcPackageArgs
, ghcCabalPackageArgs
, ghciPackageArgs
, ghcPackageArgs
, ghcPkgPackageArgs
, ghcPrimPackageArgs
, haddockPackageArgs
, haskelinePackageArgs
, integerGmpPackageArgs
, rtsPackageArgs
, runGhcPackageArgs
, disableWarningArgs
, ghcPkgPackageArgs
, haskelinePackageArgs ]
, warningArgs ]
......@@ -5,8 +5,8 @@ import Settings
basePackageArgs :: Args
basePackageArgs = package base ? do
integerLibrary <- expr integerLibraryName
mconcat [ builder GhcCabal ? arg ("--flags=" ++ integerLibrary)
integerLibraryName <- pkgName <$> getIntegerPackage
mconcat [ builder GhcCabal ? arg ("--flags=" ++ integerLibraryName)
-- This fixes the 'unknown symbol stat' issue.
-- See: https://github.com/snowleopard/hadrian/issues/259.
, builder (Ghc CompileCWithGhc) ? arg "-optc-O2" ]
......@@ -14,6 +14,7 @@ ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do
[ pure [ "-package " ++ pkgName pkg | pkg <- cabalDeps, pkg /= parsec ]
, arg "--make"
, arg "-j"
, pure ["-Wall", "-fno-warn-unused-imports", "-fno-warn-warnings-deprecations"]
, arg ("-DCABAL_VERSION=" ++ replace "." "," cabalVersion)
, arg "-DBOOTSTRAPPING"
, arg "-DMIN_VERSION_binary_0_8_0"
......
......@@ -106,6 +106,7 @@ rtsPackageArgs = package rts ? do
destDir <- expr getDestDir
let cArgs = mconcat
[ arg "-Irts"
, rtsWarnings
, arg $ "-I" ++ path
, flag UseSystemFfi ? arg ("-I" ++ ffiIncludeDir)
, arg $ "-DRtsWay=\"rts_" ++ show way ++ "\""
......@@ -198,3 +199,20 @@ rtsPackageArgs = package rts ? do
, "-DINCLUDE_DIR=\"" ++ destDir ++ ghclibDir -/- "include\"" ]
, builder HsCpp ? flag HaveLibMingwEx ? arg "-DHAVE_LIBMINGWEX" ]
-- See @rts/ghc.mk@.
rtsWarnings :: Args
rtsWarnings = mconcat
[ pure ["-Wall", "-Werror"]
, flag GccLt34 ? arg "-W", not <$> flag GccLt34 ? arg "-Wextra"
, arg "-Wstrict-prototypes"
, arg "-Wmissing-prototypes"
, arg "-Wmissing-declarations"
, arg "-Winline"
, arg "-Waggregate-return"
, arg "-Wpointer-arith"
, arg "-Wmissing-noreturn"
, arg "-Wnested-externs"
, arg "-Wredundant-decls"
, not <$> flag GccLt46 ? arg "-Wundef"
, arg "-fno-strict-aliasing" ]
module Settings.Warnings (defaultGhcWarningsArgs, warningArgs) where
import Expression
import Oracles.Flag
import Oracles.Setting
import Settings
-- See @mk/warnings.mk@ for warning-related arguments in the Make build system.
-- | Default Haskell warning-related arguments.
defaultGhcWarningsArgs :: Args
defaultGhcWarningsArgs = mconcat
[ notStage0 ? pure [ "-Werror", "-Wnoncanonical-monad-instances" ]
, (not <$> flag GccIsClang) ? mconcat
[ (not <$> flag GccLt46) ?
(not <$> windowsHost ) ? arg "-optc-Werror=unused-but-set-variable"
, (not <$> flag GccLt44) ? arg "-optc-Wno-error=inline" ]
, flag GccIsClang ? arg "-optc-Wno-unknown-pragmas" ]
-- | Package-specific warnings-related arguments, mostly suppressing various warnings.
warningArgs :: Args
warningArgs = builder Ghc ? do
isIntegerSimple <- (== integerSimple) <$> getIntegerPackage
mconcat
[ stage0 ? mconcat
[ libraryPackage ? pure [ "-fno-warn-deprecated-flags" ]
, package terminfo ? pure [ "-fno-warn-unused-imports" ]
, package transformers ? pure [ "-fno-warn-unused-matches"
, "-fno-warn-unused-imports" ] ]
, notStage0 ? mconcat
[ libraryPackage ? pure [ "-Wno-deprecated-flags" ]
, package base ? pure [ "-Wno-trustworthy-safe" ]
, package binary ? pure [ "-Wno-deprecations" ]
, package bytestring ? pure [ "-Wno-inline-rule-shadowing" ]
, package compiler ? pure [ "-Wcpp-undef" ]
, package directory ? pure [ "-Wno-unused-imports" ]
, package ghc ? pure [ "-Wcpp-undef" ]
, package ghcPrim ? pure [ "-Wno-trustworthy-safe" ]
, package haddock ? pure [ "-Wno-unused-imports"
, "-Wno-deprecations" ]
, package haskeline ? pure [ "-Wno-deprecations"
, "-Wno-unused-imports"
, "-Wno-redundant-constraints"
, "-Wno-simplifiable-class-constraints" ]
, package pretty ? pure [ "-Wno-unused-imports" ]
, package primitive ? pure [ "-Wno-unused-imports"
, "-Wno-deprecations" ]
, package rts ? pure [ "-Wcpp-undef" ]
, package terminfo ? pure [ "-Wno-unused-imports" ]
, isIntegerSimple ?
package text ? pure [ "-Wno-unused-imports" ]
, package transformers ? pure [ "-Wno-unused-matches"
, "-Wno-unused-imports"
, "-Wno-redundant-constraints"
, "-Wno-orphans" ]
, package win32 ? pure [ "-Wno-trustworthy-safe" ]
, package xhtml ? pure [ "-Wno-unused-imports" ] ] ]
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment