Skip to content

Commit ccd80e8

Browse files
committed
fix unused-top-binds unused-local-binds orphans unused-matches and unticked-promoted-constructors
1 parent 4bee82e commit ccd80e8

File tree

17 files changed

+57
-59
lines changed

17 files changed

+57
-59
lines changed

ghcide/ghcide.cabal

Lines changed: 1 addition & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -240,16 +240,11 @@ library
240240
-Wwarn=missing-signatures
241241
-Wwarn=duplicate-exports
242242
-Wwarn=dodgy-exports
243-
-Wwarn=unused-top-binds
244243
-Wwarn=incomplete-patterns
245-
-Wwarn=unused-local-binds
246-
-Wwarn=orphans
247-
-Wwarn=unused-matches
248244
-Wwarn=overlapping-patterns
249245
-Wwarn=incomplete-record-updates
250-
-Wwarn=unticked-promoted-constructors
251246

252-
if impl(ghc >= 9) && flag(pedantic)
247+
if impl(ghc >= 9.2) && flag(pedantic)
253248
ghc-options: -Wwarn=ambiguous-fields
254249

255250
if impl(ghc >= 9)

ghcide/session-loader/Development/IDE/Session.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -530,7 +530,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
530530
#if MIN_VERSION_ghc(9,3,0)
531531
let (df2, uids) = (rawComponentDynFlags, [])
532532
#else
533-
let (df2, uids) = removeInplacePackages fakeUid inplace rawComponentDynFlags
533+
let (df2, uids) = _removeInplacePackages fakeUid inplace rawComponentDynFlags
534534
#endif
535535
let prefix = show rawComponentUnitId
536536
-- See Note [Avoiding bad interface files]
@@ -1070,12 +1070,12 @@ getDependencyInfo fs = Map.fromList <$> mapM do_one fs
10701070
-- There are several places in GHC (for example the call to hptInstances in
10711071
-- tcRnImports) which assume that all modules in the HPT have the same unit
10721072
-- ID. Therefore we create a fake one and give them all the same unit id.
1073-
removeInplacePackages
1073+
_removeInplacePackages
10741074
:: UnitId -- ^ fake uid to use for our internal component
10751075
-> [UnitId]
10761076
-> DynFlags
10771077
-> (DynFlags, [UnitId])
1078-
removeInplacePackages fake_uid us df = (setHomeUnitId_ fake_uid $
1078+
_removeInplacePackages fake_uid us df = (setHomeUnitId_ fake_uid $
10791079
df { packageFlags = ps }, uids)
10801080
where
10811081
(uids, ps) = Compat.filterInplaceUnits us (packageFlags df)

ghcide/src/Development/IDE/Core/Compile.hs

Lines changed: 15 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -856,9 +856,9 @@ generateHieAsts hscEnv tcm =
856856
where
857857
dflags = hsc_dflags hscEnv
858858
#if MIN_VERSION_ghc(9,0,0)
859-
run ts =
859+
run _ts =
860860
#if MIN_VERSION_ghc(9,2,0) && !MIN_VERSION_ghc(9,3,0)
861-
fmap (join . snd) . liftIO . initDs hscEnv ts
861+
fmap (join . snd) . liftIO . initDs hscEnv _ts
862862
#else
863863
id
864864
#endif
@@ -1086,7 +1086,7 @@ mergeEnvs env mg ms extraMods envs = do
10861086
-- Prefer non-boot files over non-boot files
10871087
-- otherwise we can get errors like https://gitlab.haskell.org/ghc/ghc/-/issues/19816
10881088
-- if a boot file shadows over a non-boot file
1089-
combineModuleLocations a@(InstalledFound ml m) b | Just fp <- ml_hs_file ml, not ("boot" `isSuffixOf` fp) = a
1089+
combineModuleLocations a@(InstalledFound ml _) _ | Just fp <- ml_hs_file ml, not ("boot" `isSuffixOf` fp) = a
10901090
combineModuleLocations _ b = b
10911091

10921092
concatFC :: FinderCacheState -> [FinderCache] -> IO FinderCache
@@ -1135,9 +1135,9 @@ getModSummaryFromImports
11351135
-> UTCTime
11361136
-> Maybe Util.StringBuffer
11371137
-> ExceptT [FileDiagnostic] IO ModSummaryResult
1138-
getModSummaryFromImports env fp modTime mContents = do
1138+
getModSummaryFromImports env fp _modTime mContents = do
11391139

1140-
(contents, opts, ppEnv, src_hash) <- preprocessor env fp mContents
1140+
(contents, opts, ppEnv, _src_hash) <- preprocessor env fp mContents
11411141

11421142
let dflags = hsc_dflags ppEnv
11431143

@@ -1153,7 +1153,7 @@ getModSummaryFromImports env fp modTime mContents = do
11531153
(src_idecls, ord_idecls) = partition ((== IsBoot) . ideclSource.unLoc) imps
11541154

11551155
-- GHC.Prim doesn't exist physically, so don't go looking for it.
1156-
(ordinary_imps, ghc_prim_imports)
1156+
(ordinary_imps, _ghc_prim_imports)
11571157
= partition ((/= moduleName gHC_PRIM) . unLoc
11581158
. ideclName . unLoc)
11591159
ord_idecls
@@ -1177,7 +1177,7 @@ getModSummaryFromImports env fp modTime mContents = do
11771177
rn_imps = fmap (\(pk, lmn@(L _ mn)) -> (rn_pkg_qual mn pk, lmn))
11781178
srcImports = rn_imps $ map convImport src_idecls
11791179
textualImports = rn_imps $ map convImport (implicit_imports ++ ordinary_imps)
1180-
ghc_prim_import = not (null ghc_prim_imports)
1180+
ghc_prim_import = not (null _ghc_prim_imports)
11811181
#else
11821182
srcImports = map convImport src_idecls
11831183
textualImports = map convImport (implicit_imports ++ ordinary_imps)
@@ -1204,10 +1204,10 @@ getModSummaryFromImports env fp modTime mContents = do
12041204
#if MIN_VERSION_ghc(9,3,0)
12051205
, ms_dyn_obj_date = Nothing
12061206
, ms_ghc_prim_import = ghc_prim_import
1207-
, ms_hs_hash = src_hash
1207+
, ms_hs_hash = _src_hash
12081208

12091209
#else
1210-
, ms_hs_date = modTime
1210+
, ms_hs_date = _modTime
12111211
#endif
12121212
, ms_hsc_src = sourceType
12131213
-- The contents are used by the GetModSummary rule
@@ -1475,19 +1475,19 @@ loadInterface session ms linkableNeeded RecompilationInfo{..} = do
14751475

14761476
-- The source is modified if it is newer than the destination (iface file)
14771477
-- A more precise check for the core file is performed later
1478-
let sourceMod = case mb_dest_version of
1478+
let _sourceMod = case mb_dest_version of
14791479
Nothing -> SourceModified -- destination file doesn't exist, assume modified source
14801480
Just dest_version
14811481
| source_version <= dest_version -> SourceUnmodified
14821482
| otherwise -> SourceModified
14831483

1484-
old_iface <- case mb_old_iface of
1484+
_old_iface <- case mb_old_iface of
14851485
Just iface -> pure (Just iface)
14861486
Nothing -> do
1487-
let ncu = hsc_NC sessionWithMsDynFlags
1488-
read_dflags = hsc_dflags sessionWithMsDynFlags
1487+
let _ncu = hsc_NC sessionWithMsDynFlags
1488+
_read_dflags = hsc_dflags sessionWithMsDynFlags
14891489
#if MIN_VERSION_ghc(9,3,0)
1490-
read_result <- liftIO $ readIface read_dflags ncu mod iface_file
1490+
read_result <- liftIO $ readIface _read_dflags _ncu mod iface_file
14911491
#else
14921492
read_result <- liftIO $ initIfaceCheck (text "readIface") sessionWithMsDynFlags
14931493
$ readIface mod iface_file
@@ -1502,7 +1502,7 @@ loadInterface session ms linkableNeeded RecompilationInfo{..} = do
15021502
-- given that the source is unmodified
15031503
(recomp_iface_reqd, mb_checked_iface)
15041504
#if MIN_VERSION_ghc(9,3,0)
1505-
<- liftIO $ checkOldIface sessionWithMsDynFlags ms old_iface >>= \case
1505+
<- liftIO $ checkOldIface sessionWithMsDynFlags ms _old_iface >>= \case
15061506
UpToDateItem x -> pure (UpToDate, Just x)
15071507
OutOfDateItem reason x -> pure (NeedsRecompile reason, x)
15081508
#else

ghcide/src/Development/IDE/Core/Rules.hs

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -850,7 +850,6 @@ getModIfaceFromDiskRule recorder = defineEarlyCutoff (cmapWithPrio LogShake reco
850850
Just session -> do
851851
linkableType <- getLinkableType f
852852
ver <- use_ GetModificationTime f
853-
ShakeExtras{ideNc} <- getShakeExtras
854853
let m_old = case old of
855854
Shake.Succeeded (Just old_version) v -> Just (v, old_version)
856855
Shake.Stale _ (Just old_version) v -> Just (v, old_version)
@@ -1126,8 +1125,6 @@ getLinkableRule recorder =
11261125
Nothing -> error "called GetLinkable for a file without a linkable"
11271126
Just (bin_core, fileHash) -> do
11281127
session <- use_ GhcSessionDeps f
1129-
ShakeExtras{ideNc} <- getShakeExtras
1130-
let namecache_updater = mkUpdater ideNc
11311128
linkableType <- getLinkableType f >>= \case
11321129
Nothing -> error "called GetLinkable for a file which doesn't need compilation"
11331130
Just t -> pure t
@@ -1222,11 +1219,11 @@ computeLinkableTypeForDynFlags d
12221219
#if defined(GHC_PATCHED_UNBOXED_BYTECODE) || MIN_VERSION_ghc(9,2,0)
12231220
= BCOLinkable
12241221
#else
1225-
| unboxed_tuples_or_sums = ObjectLinkable
1222+
| _unboxed_tuples_or_sums = ObjectLinkable
12261223
| otherwise = BCOLinkable
12271224
#endif
12281225
where
1229-
unboxed_tuples_or_sums =
1226+
_unboxed_tuples_or_sums =
12301227
xopt LangExt.UnboxedTuples d || xopt LangExt.UnboxedSums d
12311228

12321229
-- | Tracks which linkables are current, so we don't need to unload them

ghcide/src/Development/IDE/Core/Shake.hs

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -994,9 +994,6 @@ usesWithStale_ key files = do
994994
newtype IdeAction a = IdeAction { runIdeActionT :: (ReaderT ShakeExtras IO) a }
995995
deriving newtype (MonadReader ShakeExtras, MonadIO, Functor, Applicative, Monad, Semigroup)
996996

997-
-- https://hub.darcs.net/ross/transformers/issue/86
998-
deriving instance (Semigroup (m a)) => Semigroup (ReaderT r m a)
999-
1000997
runIdeAction :: String -> ShakeExtras -> IdeAction a -> IO a
1001998
runIdeAction _herald s i = runReaderT (runIdeActionT i) s
1002999

ghcide/src/Development/IDE/Core/UseStale.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -82,8 +82,8 @@ dualPositionMap (PositionMap (P.PositionMapping (P.PositionDelta from to))) =
8282
-- a 'PositionMapping' that will fast-forward values to the current age.
8383
data TrackedStale a where
8484
TrackedStale
85-
:: Tracked (Stale s) a
86-
-> PositionMap (Stale s) Current
85+
:: Tracked ('Stale s) a
86+
-> PositionMap ('Stale s) 'Current
8787
-> TrackedStale a
8888

8989
instance Functor TrackedStale where
@@ -136,7 +136,7 @@ unsafeMkCurrent :: age -> Tracked 'Current age
136136
unsafeMkCurrent = coerce
137137

138138

139-
unsafeMkStale :: age -> Tracked (Stale s) age
139+
unsafeMkStale :: age -> Tracked ('Stale s) age
140140
unsafeMkStale = coerce
141141

142142

ghcide/src/Development/IDE/GHC/Compat/Core.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1084,10 +1084,10 @@ makeSimpleDetails hsc_env =
10841084
hsc_env
10851085
#endif
10861086

1087-
mkIfaceTc hsc_env sf details ms tcGblEnv =
1087+
mkIfaceTc hsc_env sf details _ms tcGblEnv =
10881088
GHC.mkIfaceTc hsc_env sf details
10891089
#if MIN_VERSION_ghc(9,3,0)
1090-
ms
1090+
_ms
10911091
#endif
10921092
tcGblEnv
10931093

ghcide/src/Development/IDE/GHC/Orphans.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ import Development.IDE.GHC.Compat
1212
import Development.IDE.GHC.Util
1313

1414
import Control.DeepSeq
15+
import Control.Monad.Trans.Reader (ReaderT (..))
1516
import Data.Aeson
1617
import Data.Hashable
1718
import Data.String (IsString (fromString))
@@ -52,6 +53,10 @@ import GHC.Types.PkgQual
5253
import GHC.Unit.Home.ModInfo
5354
#endif
5455

56+
-- Orphan instance for Shake.hs
57+
-- https://hub.darcs.net/ross/transformers/issue/86
58+
deriving instance (Semigroup (m a)) => Semigroup (ReaderT r m a)
59+
5560
-- Orphan instances for types from the GHC API.
5661
instance Show CoreModule where show = unpack . printOutputable
5762
instance NFData CoreModule where rnf = rwhnf

ghcide/src/Development/IDE/Import/FindImports.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -164,15 +164,15 @@ locateModule env comp_info exts targetFor modName mbPkgName isSource = do
164164
hpt_deps :: [UnitId]
165165
hpt_deps = homeUnitDepends units
166166
#else
167-
import_paths'
167+
_import_paths'
168168
#endif
169169

170170
-- first try to find the module as a file. If we can't find it try to find it in the package
171171
-- database.
172172
-- Here the importPaths for the current modules are added to the front of the import paths from the other components.
173173
-- This is particularly important for Paths_* modules which get generated for every component but unless you use it in
174174
-- each component will end up being found in the wrong place and cause a multi-cradle match failure.
175-
import_paths' =
175+
_import_paths' =
176176
#if MIN_VERSION_ghc(9,3,0)
177177
import_paths
178178
#else

ghcide/src/Development/IDE/LSP/LanguageServer.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -91,7 +91,7 @@ runLanguageServer
9191
-> config
9292
-> (config -> Value -> Either T.Text config)
9393
-> (MVar ()
94-
-> IO (LSP.LanguageContextEnv config -> TRequestMessage Method_Initialize -> IO (Either ResponseError (LSP.LanguageContextEnv config, a)),
94+
-> IO (LSP.LanguageContextEnv config -> TRequestMessage 'Method_Initialize -> IO (Either ResponseError (LSP.LanguageContextEnv config, a)),
9595
LSP.Handlers (m config),
9696
(LanguageContextEnv config, a) -> m config <~> IO))
9797
-> IO ()
@@ -132,7 +132,7 @@ setupLSP ::
132132
-> LSP.Handlers (ServerM config)
133133
-> (LSP.LanguageContextEnv config -> Maybe FilePath -> WithHieDb -> IndexQueue -> IO IdeState)
134134
-> MVar ()
135-
-> IO (LSP.LanguageContextEnv config -> TRequestMessage Method_Initialize -> IO (Either err (LSP.LanguageContextEnv config, IdeState)),
135+
-> IO (LSP.LanguageContextEnv config -> TRequestMessage 'Method_Initialize -> IO (Either err (LSP.LanguageContextEnv config, IdeState)),
136136
LSP.Handlers (ServerM config),
137137
(LanguageContextEnv config, IdeState) -> ServerM config <~> IO)
138138
setupLSP recorder getHieDbLoc userHandlers getIdeState clientMsgVar = do
@@ -194,7 +194,7 @@ handleInit
194194
-> (SomeLspId -> IO ())
195195
-> (SomeLspId -> IO ())
196196
-> Chan ReactorMessage
197-
-> LSP.LanguageContextEnv config -> TRequestMessage Method_Initialize -> IO (Either err (LSP.LanguageContextEnv config, IdeState))
197+
-> LSP.LanguageContextEnv config -> TRequestMessage 'Method_Initialize -> IO (Either err (LSP.LanguageContextEnv config, IdeState))
198198
handleInit recorder getHieDbLoc getIdeState lifetime exitClientMsg clearReqId waitForCancel clientMsgChan env (TRequestMessage _ _ m params) = otTracedHandler "Initialize" (show m) $ \sp -> do
199199
traceWithSpan sp params
200200
let root = LSP.resRootPath env

ghcide/src/Development/IDE/LSP/Outline.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -140,25 +140,25 @@ documentSymbolForDecl (L (locA -> (RealSrcSpan l _)) (TyClD _ DataDecl { tcdLNam
140140
}
141141
cvtFld _ = Nothing
142142
#else
143-
[ (defDocumentSymbol l :: DocumentSymbol)
143+
[ (defDocumentSymbol l'' :: DocumentSymbol)
144144
{ _name = printOutputable n
145145
, _kind = SymbolKind_Constructor
146146
, _selectionRange = realSrcSpanToRange l'
147147
, _children = conArgRecordFields (con_args x)
148148
}
149-
| L (locA -> (RealSrcSpan l _ )) x <- dd_cons
149+
| L (locA -> (RealSrcSpan l'' _ )) x <- dd_cons
150150
, L (locA -> (RealSrcSpan l' _)) n <- getConNames' x
151151
]
152152
}
153153
where
154154
-- | Extract the record fields of a constructor
155155
conArgRecordFields (RecCon (L _ lcdfs)) = Just
156-
[ (defDocumentSymbol l :: DocumentSymbol)
156+
[ (defDocumentSymbol l' :: DocumentSymbol)
157157
{ _name = printOutputable n
158158
, _kind = SymbolKind_Field
159159
}
160160
| L _ cdf <- lcdfs
161-
, L (locA -> (RealSrcSpan l _)) n <- rdrNameFieldOcc . unLoc <$> cd_fld_names cdf
161+
, L (locA -> (RealSrcSpan l' _)) n <- rdrNameFieldOcc . unLoc <$> cd_fld_names cdf
162162
]
163163
conArgRecordFields _ = Nothing
164164
#endif

ghcide/src/Development/IDE/LSP/Server.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@ import Control.Monad.IO.Unlift (MonadUnliftIO)
1414
import Control.Monad.Reader
1515
import Development.IDE.Core.Shake
1616
import Development.IDE.Core.Tracing
17-
import Ide.Types (HasTracing, traceWithSpan)
17+
import Ide.Types
1818
import Language.LSP.Protocol.Message
1919
import Language.LSP.Server (Handlers, LspM)
2020
import qualified Language.LSP.Server as LSP
@@ -30,7 +30,7 @@ newtype ServerM c a = ServerM { unServerM :: ReaderT (ReactorChan, IdeState) (Ls
3030
deriving (Functor, Applicative, Monad, MonadReader (ReactorChan, IdeState), MonadIO, MonadUnliftIO, LSP.MonadLsp c)
3131

3232
requestHandler
33-
:: forall (m :: Method ClientToServer Request) c. (HasTracing (MessageParams m)) =>
33+
:: forall m c. PluginMethod 'Request m =>
3434
SMethod m
3535
-> (IdeState -> MessageParams m -> LspM c (Either ResponseError (MessageResult m)))
3636
-> Handlers (ServerM c)
@@ -45,7 +45,7 @@ requestHandler m k = LSP.requestHandler m $ \TRequestMessage{_method,_id,_params
4545
writeChan chan $ ReactorRequest (SomeLspId _id) (trace $ LSP.runLspT env $ resp' =<< k ide _params) (LSP.runLspT env . resp' . Left)
4646

4747
notificationHandler
48-
:: forall (m :: Method ClientToServer Notification) c. (HasTracing (MessageParams m)) =>
48+
:: forall m c. PluginMethod 'Notification m =>
4949
SMethod m
5050
-> (IdeState -> VFS -> MessageParams m -> LspM c ())
5151
-> Handlers (ServerM c)

ghcide/src/Development/IDE/Plugin/HLS.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -329,11 +329,11 @@ logErrors recorder errs = do
329329

330330

331331
-- | Combine the 'PluginHandler' for all plugins
332-
newtype IdeHandler (m :: Method ClientToServer Request)
332+
newtype IdeHandler (m :: Method 'ClientToServer 'Request)
333333
= IdeHandler [(PluginId, PluginDescriptor IdeState, IdeState -> MessageParams m -> LSP.LspM Config (NonEmpty (Either PluginError (MessageResult m))))]
334334

335335
-- | Combine the 'PluginHandler' for all plugins
336-
newtype IdeNotificationHandler (m :: Method ClientToServer Notification)
336+
newtype IdeNotificationHandler (m :: Method 'ClientToServer 'Notification)
337337
= IdeNotificationHandler [(PluginId, PluginDescriptor IdeState, IdeState -> VFS -> MessageParams m -> LSP.LspM Config ())]
338338
-- type NotificationHandler (m :: Method ClientToServer Notification) = MessageParams m -> IO ()`
339339

ghcide/src/Development/IDE/Plugin/TypeLenses.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -110,7 +110,7 @@ properties = emptyProperties
110110
, (Diagnostics, "Follows error messages produced by GHC about missing signatures")
111111
] Always
112112

113-
codeLensProvider :: PluginMethodHandler IdeState Method_TextDocumentCodeLens
113+
codeLensProvider :: PluginMethodHandler IdeState 'Method_TextDocumentCodeLens
114114
codeLensProvider ideState pId CodeLensParams{_textDocument = TextDocumentIdentifier uri} = do
115115
mode <- liftIO $ runAction "codeLens.config" ideState $ usePropertyAction #mode pId properties
116116
nfp <- getNormalizedFilePathE uri
@@ -162,7 +162,7 @@ codeLensProvider ideState pId CodeLensParams{_textDocument = TextDocumentIdentif
162162
let allDiags = diags <> hDiags
163163
pure $ InL $ generateLensFromGlobalDiags allDiags
164164

165-
codeLensResolveProvider :: ResolveFunction IdeState TypeLensesResolve Method_CodeLensResolve
165+
codeLensResolveProvider :: ResolveFunction IdeState TypeLensesResolve 'Method_CodeLensResolve
166166
codeLensResolveProvider ideState pId lens@CodeLens{_range} uri TypeLensesResolve = do
167167
nfp <- getNormalizedFilePathE uri
168168
(gblSigs@(GlobalBindingTypeSigsResult _), pm) <-

ghcide/src/Development/IDE/Spans/AtPoint.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -245,9 +245,9 @@ atPoint IdeOptions{} (HAR _ hf _ _ (kind :: HieKind hietype)) (DKMap dm km) env
245245

246246
-- Check for evidence bindings
247247
isInternal :: (Identifier, IdentifierDetails a) -> Bool
248-
isInternal (Right _, dets) =
248+
isInternal (Right _, _dets) =
249249
#if MIN_VERSION_ghc(9,0,1)
250-
any isEvidenceContext $ identInfo dets
250+
any isEvidenceContext $ identInfo _dets
251251
#else
252252
False
253253
#endif

0 commit comments

Comments
 (0)