Skip to content

Commit

Permalink
Fix most -Wall in ghcide
Browse files Browse the repository at this point in the history
  • Loading branch information
jhrcek committed Jan 19, 2024
1 parent 6620f2c commit e56e2d1
Show file tree
Hide file tree
Showing 12 changed files with 45 additions and 65 deletions.
1 change: 0 additions & 1 deletion ghcide/exe/Main.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0
{-# OPTIONS_GHC -Wno-dodgy-imports #-} -- GHC no longer exports def in GHC 8.6 and above
{-# LANGUAGE TemplateHaskell #-}

module Main(main) where
Expand Down
24 changes: 13 additions & 11 deletions ghcide/ghcide.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,12 @@ flag pedantic
default: False
manual: True

common warnings
ghc-options:
-Wall -Wincomplete-uni-patterns -Wunused-packages
-Wno-unticked-promoted-constructors
-fno-ignore-asserts

library
default-language: Haskell2010
build-depends:
Expand Down Expand Up @@ -218,10 +224,6 @@ library
Development.IDE.Session.VersionCheck
Development.IDE.Types.Action

ghc-options:
-Wall -Wincomplete-uni-patterns -Wno-unticked-promoted-constructors
-Wunused-packages -fno-ignore-asserts

if flag(pedantic)
-- We eventually want to build with Werror fully, but we haven't
-- finished purging the warnings, so some are set to not be errors
Expand All @@ -246,9 +248,10 @@ flag test-exe
default: True

executable ghcide-test-preprocessor
import: warnings
default-language: Haskell2010
hs-source-dirs: test/preprocessor
ghc-options: -Wall -Wno-name-shadowing
ghc-options: -Wno-name-shadowing
main-is: Main.hs
build-depends: base >=4 && <5

Expand All @@ -260,11 +263,11 @@ flag executable
default: True

executable ghcide
import: warnings
default-language: Haskell2010
hs-source-dirs: exe
ghc-options:
-threaded -Wall -Wincomplete-uni-patterns -Wno-name-shadowing -Wunused-packages
-rtsopts "-with-rtsopts=-I0 -A128M -T"
ghc-options: -threaded -rtsopts "-with-rtsopts=-I0 -A128M -T" -Wno-name-shadowing


-- allow user RTS overrides
-- disable idle GC
Expand Down Expand Up @@ -314,6 +317,7 @@ executable ghcide
cpp-options: -DMONITORING_EKG

test-suite ghcide-tests
import: warnings
type: exitcode-stdio-1.0
default-language: Haskell2010
build-tool-depends:
Expand Down Expand Up @@ -371,9 +375,7 @@ test-suite ghcide-tests
build-depends: ghc-typelits-knownnat

hs-source-dirs: test/cabal test/exe test/src
ghc-options:
-threaded -Wall -Wno-name-shadowing -O0
-Wno-unticked-promoted-constructors -Wunused-packages
ghc-options: -threaded -O0 -Wno-name-shadowing

main-is: Main.hs
other-modules:
Expand Down
41 changes: 15 additions & 26 deletions ghcide/src/Development/IDE/GHC/Compat.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,19 +5,15 @@
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PatternSynonyms #-}
{-# OPTIONS -Wno-incomplete-uni-patterns -Wno-dodgy-imports #-}

-- | Attempt at hiding the GHC version differences we can.
module Development.IDE.GHC.Compat(
mkHomeModLocation,
hPutStringBuffer,
addIncludePathsQuote,
getModuleHash,
setUpTypedHoles,
NameCacheUpdater(..),
#if MIN_VERSION_ghc(9,3,0)
getMessages,
renderDiagnosticMessageWithHints,
nameEnvElts,
#else
upNameCache,
Expand All @@ -26,10 +22,8 @@ module Development.IDE.GHC.Compat(
disableWarningsAsErrors,
reLoc,
reLocA,
getPsMessages,
renderMessages,
pattern PFailedWithErrorMessages,
isObjectLinkable,

#if !MIN_VERSION_ghc(9,3,0)
extendModSummaryNoDeps,
Expand All @@ -53,8 +47,9 @@ module Development.IDE.GHC.Compat(
nodeAnnotations,
mkAstNode,
combineRealSrcSpans,

#if !MIN_VERSION_ghc(9,3,0)
nonDetOccEnvElts,
#endif
nonDetFoldOccEnv,

isQualifiedImport,
Expand Down Expand Up @@ -94,7 +89,9 @@ module Development.IDE.GHC.Compat(
simplifyExpr,
tidyExpr,
emptyTidyEnv,
#if MIN_VERSION_ghc(9,7,0)
tcInitTidyEnv,
#endif
corePrepExpr,
corePrepPgm,
lintInteractiveExpr,
Expand Down Expand Up @@ -160,11 +157,6 @@ import Data.List (foldl')
import qualified Data.Map as Map
import qualified Data.Set as S

-- See Note [Guidelines For Using CPP In GHCIDE Import Statements]

#if MIN_VERSION_ghc(9,7,0)
import GHC.Tc.Zonk.TcType (tcInitTidyEnv)
#endif
import qualified GHC.Core.Opt.Pipeline as GHC
import GHC.Core.Tidy (tidyExpr)
import GHC.CoreToStg.Prep (corePrepPgm)
Expand All @@ -187,15 +179,8 @@ import GHC.Iface.Make (mkIfaceExports)
import GHC.SysTools.Tasks (runUnlit, runPp)
import qualified GHC.Types.Avail as Avail


#if !MIN_VERSION_ghc(9,5,0)
import GHC.Core.Lint (lintInteractiveExpr)
#endif


import GHC.Iface.Env
import GHC.Types.SrcLoc (combineRealSrcSpans)
import GHC.Linker.Loader (loadExpr)
import GHC.Runtime.Context (icInteractiveModule)
import GHC.Unit.Home.ModInfo (HomePackageTable,
lookupHpt)
Expand All @@ -205,21 +190,19 @@ import GHC.Builtin.Uniques
import GHC.ByteCode.Types
import GHC.CoreToStg
import GHC.Data.Maybe
import GHC.Linker.Loader (loadDecls)
import GHC.Linker.Loader (loadDecls, loadExpr)
import GHC.Stg.Pipeline
import GHC.Stg.Syntax
import GHC.StgToByteCode
import GHC.Types.CostCentre
import GHC.Types.IPE

-- See Note [Guidelines For Using CPP In GHCIDE Import Statements]

#if !MIN_VERSION_ghc(9,3,0)
import GHC.Unit.Module.Deps (Dependencies(dep_mods), Usage(..))
import GHC.Linker.Types (isObjectLinkable)
import GHC.Unit.Module.ModSummary
import GHC.Runtime.Interpreter
#endif

#if !MIN_VERSION_ghc(9,3,0)
import Data.IORef
#endif

Expand All @@ -228,6 +211,10 @@ import GHC.Unit.Module.Deps (Dependencies(dep_direct_mods), Usage(..))
import GHC.Driver.Config.Stg.Pipeline
#endif

#if !MIN_VERSION_ghc(9,5,0)
import GHC.Core.Lint (lintInteractiveExpr)
#endif

#if MIN_VERSION_ghc(9,5,0)
import GHC.Core.Lint.Interactive (interactiveInScope)
import GHC.Driver.Config.Core.Lint.Interactive (lintInteractiveExpr)
Expand All @@ -236,12 +223,14 @@ import GHC.Driver.Config.CoreToStg (initCoreTo
import GHC.Driver.Config.CoreToStg.Prep (initCorePrepConfig)
#endif

#if MIN_VERSION_ghc(9,7,0)
import GHC.Tc.Zonk.TcType (tcInitTidyEnv)
#endif

#if !MIN_VERSION_ghc(9,7,0)
liftZonkM :: a -> a
liftZonkM = id
#endif

#if !MIN_VERSION_ghc(9,7,0)
nonDetFoldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b
nonDetFoldOccEnv = foldOccEnv
#endif
Expand Down
25 changes: 10 additions & 15 deletions ghcide/src/Development/IDE/GHC/Compat/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE ViewPatterns #-}

-- | Compat Core module that handles the GHC module hierarchy re-organization
-- by re-exporting everything we care about.
Expand Down Expand Up @@ -85,7 +85,6 @@ module Development.IDE.GHC.Compat.Core (
RecompileRequired(..),
mkPartialIface,
mkFullIface,
checkOldIface,
IsBootInterface(..),
-- * Fixity
LexicalFixity(..),
Expand Down Expand Up @@ -120,14 +119,14 @@ module Development.IDE.GHC.Compat.Core (
pattern ConPatIn,
conPatDetails,
mapConPatDetail,
#if MIN_VERSION_ghc(9,5,0)
mkVisFunTys,
#endif
-- * Specs
ImpDeclSpec(..),
ImportSpec(..),
-- * SourceText
SourceText(..),
-- * Name
tyThingParent_maybe,
-- * Ways
Way,
wayGeneralFlags,
Expand Down Expand Up @@ -168,6 +167,7 @@ module Development.IDE.GHC.Compat.Core (
hscInteractive,
hscSimplify,
hscTypecheckRename,
hscUpdateHPT,
Development.IDE.GHC.Compat.Core.makeSimpleDetails,
-- * Typecheck utils
tcSplitForAllTyVars,
Expand All @@ -176,7 +176,6 @@ module Development.IDE.GHC.Compat.Core (
Development.IDE.GHC.Compat.Core.mkIfaceTc,
Development.IDE.GHC.Compat.Core.mkBootModDetailsTc,
Development.IDE.GHC.Compat.Core.initTidyOpts,
hscUpdateHPT,
driverNoStop,
tidyProgram,
ImportedModsVal(..),
Expand Down Expand Up @@ -204,7 +203,6 @@ module Development.IDE.GHC.Compat.Core (
pattern RealSrcLoc,
SrcLoc.SrcLoc(SrcLoc.UnhelpfulLoc),
BufSpan,
SrcSpanAnn',
GHC.SrcAnn,
SrcLoc.leftmost_smallest,
SrcLoc.containsSpan,
Expand Down Expand Up @@ -236,7 +234,6 @@ module Development.IDE.GHC.Compat.Core (
-- * Finder
FindResult(..),
mkHomeModLocation,
addBootSuffixLocnOut,
findObjectLinkableMaybe,
InstalledFindResult(..),
-- * Module and Package
Expand All @@ -263,7 +260,6 @@ module Development.IDE.GHC.Compat.Core (
Target(..),
TargetId(..),
mkSimpleTarget,
mkModuleGraph,
-- * GHCi
initObjLinker,
loadDLL,
Expand All @@ -285,8 +281,6 @@ module Development.IDE.GHC.Compat.Core (
Role(..),
-- * Panic
Plain.PlainGhcException,
panic,
panicDoc,
-- * Other
GHC.CoreModule(..),
GHC.SafeHaskellMode(..),
Expand Down Expand Up @@ -344,7 +338,7 @@ module Development.IDE.GHC.Compat.Core (

module GHC.Types.Basic,
module GHC.Types.Id,
module GHC.Types.Name ,
module GHC.Types.Name,
module GHC.Types.Name.Set,

module GHC.Types.Name.Cache,
Expand All @@ -370,7 +364,7 @@ module Development.IDE.GHC.Compat.Core (
#if MIN_VERSION_ghc(9,3,0)
CompileReason(..),
hsc_type_env_vars,
hscUpdateHUG, hscUpdateHPT, hsc_HUG,
hscUpdateHUG, hsc_HUG,
GhcMessage(..),
getKey,
module GHC.Driver.Env.KnotVars,
Expand All @@ -396,19 +390,20 @@ module Development.IDE.GHC.Compat.Core (
#else
Extension(..),
#endif
UniqFM,
mkCgInteractiveGuts,
justBytecode,
justObjects,
emptyHomeModInfoLinkable,
homeModInfoByteCode,
homeModInfoObject,
# if !MIN_VERSION_ghc(9,5,0)
#if !MIN_VERSION_ghc(9,5,0)
field_label,
#endif
groupOrigin,
isVisibleFunArg,
lookupGlobalRdrEnv,
#if MIN_VERSION_ghc(9,8,0)
lookupGlobalRdrEnv
#endif
) where

import qualified GHC
Expand Down
1 change: 0 additions & 1 deletion ghcide/test/exe/CodeLensTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,6 @@ import qualified Data.Text as T
import Data.Tuple.Extra
import Development.IDE.GHC.Compat (GhcVersion (..), ghcVersion)
import qualified Language.LSP.Protocol.Lens as L
import Language.LSP.Protocol.Message
import Language.LSP.Protocol.Types hiding
(SemanticTokenAbsolute (..),
SemanticTokenRelative (..),
Expand Down
1 change: 0 additions & 1 deletion ghcide/test/exe/CompletionTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -550,7 +550,6 @@ completionDocTests =
test doc (Position 1 7) "id" (Just $ T.length expected) [expected]
]
where
brokenForGhc9 = knownBrokenFor (BrokenForGHC [GHC90, GHC92, GHC94, GHC96]) "Completion doc doesn't support ghc9"
brokenForWinGhc90 = knownBrokenFor (BrokenSpecific Windows [GHC90]) "Extern doc doesn't support Windows for ghc9.2"
-- https://gitlab.haskell.org/ghc/ghc/-/issues/20903
brokenForMacGhc9 = knownBrokenFor (BrokenSpecific MacOS [GHC90, GHC92, GHC94, GHC96]) "Extern doc doesn't support MacOS for ghc9"
Expand Down
4 changes: 2 additions & 2 deletions ghcide/test/exe/FindDefinitionAndHoverTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ import Language.LSP.Protocol.Types hiding
import Language.LSP.Test
import System.FilePath
import System.Info.Extra (isWindows)
-- import Test.QuickCheck.Instances ()

import Control.Lens ((^.))
import Test.Tasty
import Test.Tasty.HUnit
Expand Down Expand Up @@ -240,7 +240,7 @@ tests = let
yes = Just -- test should run and pass
broken = Just . (`xfail` "known broken")
no = const Nothing -- don't run this test at all
skip = const Nothing -- unreliable, don't run
--skip = const Nothing -- unreliable, don't run

checkFileCompiles :: FilePath -> Session () -> TestTree
checkFileCompiles fp diag =
Expand Down
1 change: 0 additions & 1 deletion ghcide/test/exe/HieDbRetry.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,6 @@ errorBusy = SQLite.SQLError{ sqlError = SQLite.ErrorBusy, sqlErrorDetails = "",
isErrorCall :: ErrorCall -> Maybe ErrorCall
isErrorCall e
| ErrorCall _ <- e = Just e
| otherwise = Nothing

tests :: TestTree
tests = testGroup "RetryHieDb"
Expand Down
2 changes: 1 addition & 1 deletion ghcide/test/exe/HighlightTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module HighlightTests (tests) where

import Control.Monad.IO.Class (liftIO)
import qualified Data.Text as T
import Development.IDE.GHC.Compat (GhcVersion (..), ghcVersion)
import Development.IDE.GHC.Compat (GhcVersion (..))
import Development.IDE.Types.Location
import Language.LSP.Protocol.Types hiding
(SemanticTokenAbsolute (..),
Expand Down
2 changes: 1 addition & 1 deletion ghcide/test/exe/InitializeResponseTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ import Language.LSP.Protocol.Types hiding
SemanticTokensEdit (..),
mkRange)
import Language.LSP.Test
-- import Test.QuickCheck.Instances ()

import Control.Lens ((^.))
import Development.IDE.Plugin.Test (blockCommandId)
import Test.Tasty
Expand Down
Loading

0 comments on commit e56e2d1

Please sign in to comment.