Skip to content

Commit

Permalink
Ignore -Werror
Browse files Browse the repository at this point in the history
Fixes #735
  • Loading branch information
pepeiborra committed Aug 23, 2020
1 parent 7538e36 commit 26a61cf
Show file tree
Hide file tree
Showing 4 changed files with 39 additions and 3 deletions.
1 change: 1 addition & 0 deletions session-loader/Development/IDE/Session.hs
Original file line number Diff line number Diff line change
Expand Up @@ -566,6 +566,7 @@ setOptions :: GhcMonad m => ComponentOptions -> DynFlags -> m (DynFlags, [Target
setOptions (ComponentOptions theOpts compRoot _) dflags = do
(dflags', targets) <- addCmdOpts theOpts dflags
let dflags'' =
disableWarningsAsErrors $
-- disabled, generated directly by ghcide instead
flip gopt_unset Opt_WriteInterface $
-- disabled, generated directly by ghcide instead
Expand Down
3 changes: 2 additions & 1 deletion src/Development/IDE/Core/Preprocessor.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ import qualified HeaderInfo as Hdr
import Development.IDE.Types.Diagnostics
import Development.IDE.Types.Location
import Development.IDE.GHC.Error
import Development.IDE.GHC.Util
import SysTools (Option (..), runUnlit, runPp)
import Control.Monad.Trans.Except
import qualified GHC.LanguageExtensions as LangExt
Expand Down Expand Up @@ -145,7 +146,7 @@ parsePragmasIntoDynFlags fp contents = catchSrcErrors "pragmas" $ do
liftIO $ evaluate $ rnf opts

(dflags, _, _) <- parseDynamicFilePragma dflags0 opts
return dflags
return $ disableWarningsAsErrors dflags


-- | Run (unlit) literate haskell preprocessor on a file, or buffer if set
Expand Down
8 changes: 7 additions & 1 deletion src/Development/IDE/GHC/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@ module Development.IDE.GHC.Util(
hDuplicateTo',
setHieDir,
dontWriteHieFiles,
disableWarningsAsErrors,
) where

import Control.Concurrent
Expand Down Expand Up @@ -66,7 +67,7 @@ import Outputable (showSDocUnsafe, ppr, showSDoc, Outputable)
import Packages (getPackageConfigMap, lookupPackage')
import SrcLoc (mkRealSrcLoc)
import FastString (mkFastString)
import DynFlags (emptyFilesToClean, unsafeGlobalDynFlags)
import DynFlags (wopt_unset_fatal, gopt_unset, emptyFilesToClean, unsafeGlobalDynFlags)
import Module (moduleNameSlashes, InstalledUnitId)
import OccName (parenSymOcc)
import RdrName (nameRdrName, rdrNameOcc)
Expand Down Expand Up @@ -310,3 +311,8 @@ ioe_dupHandlesNotCompatible :: Handle -> IO a
ioe_dupHandlesNotCompatible h =
ioException (IOError (Just h) IllegalOperation "hDuplicateTo"
"handles are incompatible" Nothing Nothing)


disableWarningsAsErrors :: DynFlags -> DynFlags
disableWarningsAsErrors df = flip gopt_unset Opt_WarnIsError
$ foldl' wopt_unset_fatal df [toEnum 0 ..]
30 changes: 29 additions & 1 deletion test/exe/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -468,6 +468,34 @@ diagnosticTests = testGroup "diagnostics"
Lens.filtered (T.isInfixOf ("/" <> name <> ".hs:"))
failure msg = liftIO $ assertFailure $ "Expected file path to be stripped but got " <> T.unpack msg
Lens.mapMOf_ offenders failure notification
, testSession' "-Werror in cradle is ignored" $ \sessionDir -> do
liftIO $ writeFile (sessionDir </> "hie.yaml")
"cradle: {direct: {arguments: [\"-Wall\", \"-Werror\"]}}"
let fooContent = T.unlines
[ "module Foo where"
, "foo = ()"
]
_ <- createDoc "Foo.hs" "haskell" fooContent
expectDiagnostics
[ ( "Foo.hs"
, [(DsWarning, (1, 0), "Top-level binding with no type signature:")
]
)
]
, testSessionWait "-Werror in pragma is ignored" $ do
let fooContent = T.unlines
[ "{-# OPTIONS_GHC -Wall -Werror #-}"
, "module Foo() where"
, "foo :: Int"
, "foo = 1"
]
_ <- createDoc "Foo.hs" "haskell" fooContent
expectDiagnostics
[ ( "Foo.hs"
, [(DsWarning, (3, 0), "Defined but not used:")
]
)
]
]

codeActionTests :: TestTree
Expand Down Expand Up @@ -3031,7 +3059,7 @@ mkRange :: Int -> Int -> Int -> Int -> Range
mkRange a b c d = Range (Position a b) (Position c d)

run :: Session a -> IO a
run s = withTempDir $ \dir -> runInDir dir s
run s = run' (const s)

runWithExtraFiles :: FilePath -> (FilePath -> Session a) -> IO a
runWithExtraFiles prefix s = withTempDir $ \dir -> do
Expand Down

0 comments on commit 26a61cf

Please sign in to comment.