Cleanup disabled warnings (#4341)

* Cleanup unnecessarily disabled warnings

* Fix stack nighly build

* stylish
This commit is contained in:
Jan Hrcek 2024-06-28 16:38:40 +02:00 committed by GitHub
parent 147fb4a291
commit 124691f950
No known key found for this signature in database
GPG Key ID: B5690EEEBB952194
10 changed files with 31 additions and 64 deletions

View File

@ -38,7 +38,6 @@ module Development.IDE.Core.Compile
, shareUsages
) where
import Control.Concurrent.Extra
import Control.Concurrent.STM.Stats hiding (orElse)
import Control.DeepSeq (NFData (..), force,
rnf)
@ -72,8 +71,7 @@ import Data.Tuple.Extra (dupe)
import Debug.Trace
import Development.IDE.Core.FileStore (resetInterfaceStore)
import Development.IDE.Core.Preprocessor
import Development.IDE.Core.ProgressReporting (ProgressReporting (..),
progressReportingOutsideState)
import Development.IDE.Core.ProgressReporting (ProgressReporting (..))
import Development.IDE.Core.RuleTypes
import Development.IDE.Core.Shake
import Development.IDE.Core.Tracing (withTrace)

View File

@ -1,7 +1,7 @@
-- "missing signature" is declared a fatal warning in the cabal file,
-- but is ignored in this module.
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
{-# OPTIONS_GHC -Wno-missing-signatures #-}
module IgnoreFatal where

View File

@ -1,7 +1,7 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wwarn -fno-warn-orphans #-}
{-# OPTIONS_GHC -Wwarn #-}
-- | Expression execution
module Ide.Plugin.Eval.Code (Statement, testRanges, resultRange, propSetup, testCheck, asStatements,myExecStmt) where

View File

@ -5,7 +5,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fno-warn-type-defaults -Wno-unused-imports #-}
{-# OPTIONS_GHC -Wno-type-defaults #-}
{- |
A plugin inspired by the REPLoid feature of <https://github.com/jyp/dante Dante>, <https://www.haskell.org/haddock/doc/html/ch03s08.html#idm140354810775744 Haddock>'s Examples and Properties and <https://hackage.haskell.org/package/doctest Doctest>.
@ -18,13 +18,12 @@ module Ide.Plugin.Eval.CodeLens (
) where
import Control.Applicative (Alternative ((<|>)))
import Control.Arrow (second, (>>>))
import Control.Exception (bracket_, try)
import Control.Arrow (second)
import Control.Exception (bracket_)
import qualified Control.Exception as E
import Control.Lens (_1, _3, ix, (%~),
(<&>), (^.))
import Control.Monad (guard, join,
void, when)
import Control.Lens (ix, (%~), (^.))
import Control.Monad (guard, void,
when)
import Control.Monad.IO.Class (MonadIO (liftIO))
import Control.Monad.Trans.Except (ExceptT (..),
runExceptT)
@ -44,25 +43,18 @@ import Data.Typeable (Typeable)
import Development.IDE.Core.Rules (IdeState,
runAction)
import Development.IDE.Core.RuleTypes (LinkableResult (linkableHomeMod),
NeedsCompilation (NeedsCompilation),
TypeCheck (..),
tmrTypechecked)
import Development.IDE.Core.Shake (shakeExtras,
useNoFile_,
useWithStale_,
use_, uses_)
import Development.IDE.Core.Shake (useNoFile_, use_,
uses_)
import Development.IDE.GHC.Compat hiding (typeKind,
unitState)
import Development.IDE.GHC.Compat.Util (GhcException,
OverridingBool (..),
bagToList)
import Development.IDE.GHC.Compat.Util (OverridingBool (..))
import Development.IDE.GHC.Util (evalGhcEnv,
modifyDynFlags,
printOutputable)
modifyDynFlags)
import Development.IDE.Import.DependencyInformation (transitiveDeps,
transitiveModuleDeps)
import Development.IDE.Types.Location (toNormalizedFilePath',
uriToFilePath')
import Development.IDE.Types.Location (toNormalizedFilePath')
import GHC (ClsInst,
ExecOptions (execLineNumber, execSourceFile),
FamInst,
@ -87,15 +79,12 @@ import Development.IDE.Core.RuleTypes (GetLinkable (GetL
ModSummaryResult (msrModSummary))
import Development.IDE.Core.Shake (VFSModified (VFSUnmodified))
import qualified Development.IDE.GHC.Compat.Core as Compat (InteractiveImport (IIModule))
import qualified Development.IDE.GHC.Compat.Core as SrcLoc (HasSrcSpan (getLoc),
unLoc)
import qualified Development.IDE.GHC.Compat.Core as SrcLoc (unLoc)
import Development.IDE.Types.HscEnvEq (HscEnvEq (hscEnv))
import qualified GHC.LanguageExtensions.Type as LangExt (Extension (..))
import Control.Concurrent.STM.Stats (atomically)
import Development.IDE.Core.FileStore (setSomethingModified)
import Development.IDE.Core.PluginUtils
import Development.IDE.Graph (ShakeOptions (shakeExtra))
import Development.IDE.Types.Shake (toKey)
import GHC.Types.SrcLoc (UnhelpfulSpanReason (UnhelpfulInteractive))
import Ide.Logger (Priority (..),
@ -103,7 +92,6 @@ import Ide.Logger (Priority (..),
WithPriority,
logWith)
import Ide.Plugin.Error (PluginError (PluginInternalError),
handleMaybe,
handleMaybeM)
import Ide.Plugin.Eval.Code (Statement,
asStatements,
@ -117,8 +105,7 @@ import Ide.Plugin.Eval.Config (EvalConfig (..),
import Ide.Plugin.Eval.GHC (addImport,
addPackages,
hasPackage,
setSessionAndInteractiveDynFlags,
showDynFlags)
setSessionAndInteractiveDynFlags)
import Ide.Plugin.Eval.Parse.Comments (commentsToSections)
import Ide.Plugin.Eval.Parse.Option (parseSetFlags)
import Ide.Plugin.Eval.Rules (queueForEvaluation,

View File

@ -1,6 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# OPTIONS_GHC -fno-warn-unused-imports -Wno-orphans #-}
{-# OPTIONS_GHC -Wno-orphans #-}
-- |GHC API utilities
module Ide.Plugin.Eval.GHC (

View File

@ -1,9 +1,8 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# OPTIONS_GHC -Wno-orphans -Wno-unused-imports #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -Wno-orphans #-}
-- |Debug utilities
-- | Debug utilities
module Ide.Plugin.Eval.Util (
timed,
isLiterate,
@ -15,39 +14,31 @@ module Ide.Plugin.Eval.Util (
import Control.Exception (SomeException, evaluate,
fromException)
import Control.Monad.Error.Class (MonadError (throwError))
import Control.Monad.IO.Class (MonadIO (liftIO))
import Control.Monad.Trans.Class (MonadTrans (lift))
import Control.Monad.Trans.Except (ExceptT (..),
runExceptT)
import Data.Aeson (Value)
import Data.Bifunctor (second)
import Data.String (IsString (fromString))
import qualified Data.Text as T
import Development.IDE (IdeState,
printOutputable)
import qualified Development.IDE.Core.PluginUtils as PluginUtils
import qualified Development.IDE.GHC.Compat.Core as Core
import qualified Development.IDE.GHC.Compat.Core as SrcLoc
import Development.IDE.GHC.Compat.Outputable
import Development.IDE.GHC.Compat.Util (MonadCatch, bagToList,
catch)
import GHC.Exts (toList)
import GHC.Stack (HasCallStack, callStack,
srcLocFile,
srcLocStartCol,
srcLocStartLine)
import Ide.Plugin.Error
import Ide.Types (HandlerM,
pluginSendRequest)
import Language.LSP.Protocol.Message
import Language.LSP.Protocol.Types
import Language.LSP.Server
import System.FilePath (takeExtension)
import qualified System.Time.Extra as Extra
import System.Time.Extra (duration, showDuration)
import System.Time.Extra (duration)
import UnliftIO.Exception (catchAny)
#if !MIN_VERSION_ghc(9,8,0)
import qualified Data.Text as T
import Development.IDE (printOutputable)
import qualified Development.IDE.GHC.Compat.Core as Core
#endif
timed :: MonadIO m => (t -> Extra.Seconds -> m a) -> t -> m b -> m b
timed out name op = do
(secs, r) <- duration op
@ -107,6 +98,6 @@ prettyWarnings = unlines . map prettyWarn
prettyWarn :: Core.Warn -> String
prettyWarn Core.Warn{..} =
T.unpack (printOutputable $ SrcLoc.getLoc warnMsg) <> ": warning:\n"
<> " " <> SrcLoc.unLoc warnMsg
T.unpack (printOutputable $ Core.getLoc warnMsg) <> ": warning:\n"
<> " " <> Core.unLoc warnMsg
#endif

View File

@ -13,11 +13,6 @@
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-orphans #-}
-- On 9.4 we get a new redundant constraint warning, but deleting the
-- constraint breaks the build on earlier versions. Rather than apply
-- lots of CPP, we just disable the warning until later.
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
#ifdef GHC_LIB
#define MIN_GHC_API_VERSION(x,y,z) MIN_VERSION_ghc_lib_parser(x,y,z)
#else

View File

@ -4,8 +4,6 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wwarn -fno-warn-type-defaults #-}
{- | Keep the module name in sync with its file path.
Provide CodeLenses to:

View File

@ -3,7 +3,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-dodgy-imports #-} -- GHC no longer exports def in GHC 8.6 and above
module Ide.Arguments
( Arguments(..)

View File

@ -1,7 +1,6 @@
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -Wno-dodgy-imports #-} -- GHC no longer exports def in GHC 8.6 and above
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
@ -18,7 +17,7 @@ import Data.Text (Text)
import qualified Data.Text as T
import Data.Text.Lazy.Encoding (decodeUtf8)
import qualified Data.Text.Lazy.IO as LT
import Development.IDE.Core.Rules hiding (Log, logToPriority)
import Development.IDE.Core.Rules hiding (Log)
import Development.IDE.Core.Tracing (withTelemetryRecorder)
import Development.IDE.Main (isLSP)
import qualified Development.IDE.Main as IDEMain