Skip to content

Commit 9f22ed6

Browse files
committed
Hlint: Automatically fix warnings via apply-refact
1 parent af972dc commit 9f22ed6

File tree

15 files changed

+25
-25
lines changed

15 files changed

+25
-25
lines changed

bench/Main.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,6 @@
4444
{-# LANGUAGE DerivingStrategies #-}
4545
{-# LANGUAGE TypeFamilies #-}
4646
{-# OPTIONS -Wno-orphans #-}
47-
{-# LANGUAGE PackageImports #-}
4847

4948
import Control.Lens (preview, (^.))
5049
import Control.Monad.Extra

exe/Wrapper.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -12,11 +12,11 @@
1212
module Main where
1313

1414
import Control.Monad.Extra
15-
import Data.Char (isSpace)
1615
import Data.Default
1716
import Data.Either.Extra (eitherToMaybe)
1817
import Data.Foldable
1918
import Data.List
19+
import Data.List.Extra (trimEnd)
2020
import Data.Void
2121
import qualified Development.IDE.Session as Session
2222
import qualified HIE.Bios.Environment as HieBios
@@ -232,7 +232,7 @@ findProjectCradle' log = do
232232
trim :: String -> String
233233
trim s = case lines s of
234234
[] -> s
235-
ls -> dropWhileEnd isSpace $ last ls
235+
ls -> trimEnd $ last ls
236236

237237
data WrapperSetupError
238238
= FailedToObtainGhcVersion (ActionName Void) CradleError

ghcide-bench/src/Experiments.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -538,7 +538,7 @@ runBench runSess b = handleAny (\e -> print e >> return badRun)
538538
output (showDuration t)
539539
-- Wait for the delayed actions to finish
540540
td <- waitForBuildQueue
541-
loop' (timeForFirstResponse <|> (Just (t,td))) (userWaits+t) (delayedWork+td) (n -1)
541+
loop' (timeForFirstResponse <|> Just (t,td)) (userWaits+t) (delayedWork+td) (n -1)
542542
loop = loop' Nothing
543543

544544
(runExperiment, result) <- duration $ loop 0 0 samples

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

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -308,7 +308,7 @@ captureSplicesAndDeps TypecheckHelpers{..} env k = do
308308
mods_transitive = getTransitiveMods hsc_env needed_mods
309309

310310
-- If we don't support multiple home units, ModuleNames are sufficient because all the units will be the same
311-
mods_transitive_list =
311+
mods_transitive_list =
312312
#if MIN_VERSION_ghc(9,3,0)
313313
mapMaybe nodeKeyToInstalledModule $ Set.toList mods_transitive
314314
#else
@@ -362,7 +362,7 @@ captureSplicesAndDeps TypecheckHelpers{..} env k = do
362362
#endif
363363

364364
-- Compute the transitive set of linkables required
365-
getTransitiveMods hsc_env needed_mods
365+
getTransitiveMods hsc_env needed_mods
366366
#if MIN_VERSION_ghc(9,3,0)
367367
= Set.unions (Set.fromList (map moduleToNodeKey mods) : [ dep | m <- mods
368368
, Just dep <- [Map.lookup (moduleToNodeKey m) (mgTransDeps (hsc_mod_graph hsc_env))]
@@ -561,7 +561,7 @@ mkHiFileResultCompile se session' tcm simplified_guts = catchErrs $ do
561561

562562

563563
when (not $ null diffs) $
564-
panicDoc "verify core failed!" (vcat $ punctuate (text "\n\n") (diffs )) -- ++ [ppr binds , ppr binds']))
564+
panicDoc "verify core failed!" (vcat $ punctuate (text "\n\n") diffs) -- ++ [ppr binds , ppr binds']))
565565
_ -> pure ()
566566

567567
pure ([], Just $! mkHiFileResult ms final_iface details (tmrRuntimeModules tcm) core_file)

ghcide/src/Development/IDE/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -283,7 +283,7 @@ testing recorder logger =
283283
hlsPlugins = pluginDescToIdePlugins $
284284
idePluginsToPluginDesc argsHlsPlugins
285285
++ [Test.blockCommandDescriptor "block-command", Test.plugin]
286-
ideOptions = \config sessionLoader ->
286+
ideOptions config sessionLoader =
287287
let
288288
defOptions = argsIdeOptions config sessionLoader
289289
in

hie-compat/src-ghc86/Compat/HieDebug.hs

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
{-
22
Functions to validate and check .hie file ASTs generated by GHC.
33
-}
4-
{-# LANGUAGE StandaloneDeriving #-}
4+
55
{-# LANGUAGE OverloadedStrings #-}
66
{-# LANGUAGE FlexibleContexts #-}
77
module Compat.HieDebug where
@@ -129,9 +129,7 @@ validateScopes asts = M.foldrWithKey (\k a b -> valid k a ++ b) [] refMap
129129
valid (Right n) refs = concatMap inScope refs
130130
where
131131
mapRef = foldMap getScopeFromContext . identInfo . snd
132-
scopes = case foldMap mapRef refs of
133-
Just xs -> xs
134-
Nothing -> []
132+
scopes = Data.Maybe.fromMaybe [] (foldMap mapRef refs)
135133
inScope (sp, dets)
136134
| definedInAsts asts n
137135
&& any isOccurrence (identInfo dets)

hie-compat/src-ghc86/Compat/HieTypes.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ For more information see https://gitlab.haskell.org/ghc/ghc/wikis/hie-files
55
-}
66
{-# LANGUAGE DeriveTraversable #-}
77
{-# LANGUAGE DeriveDataTypeable #-}
8-
{-# LANGUAGE TypeSynonymInstances #-}
8+
99
{-# LANGUAGE FlexibleInstances #-}
1010
{-# LANGUAGE ScopedTypeVariables #-}
1111
{-# OPTIONS_GHC -Wno-orphans #-}

hie-compat/src-ghc86/Compat/HieUtils.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -127,7 +127,7 @@ recoverFullType i m = go i
127127

128128
getTypeIndex :: Type -> State HieTypeState TypeIndex
129129
getTypeIndex t
130-
| otherwise = do
130+
= do
131131
tm <- gets tyMap
132132
case lookupTypeMap tm t of
133133
Just i -> return i

hls-graph/src/Development/IDE/Graph/Internal/Database.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
-- We deliberately want to ensure the function we add to the rule database
22
-- has the constraints we need on it when we get it out.
33
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
4-
{-# LANGUAGE DeriveFunctor #-}
4+
55
{-# LANGUAGE DerivingStrategies #-}
66
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
77
{-# LANGUAGE RankNTypes #-}

hls-plugin-api/src/Ide/Plugin/ConfigUtils.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ import qualified Data.Aeson.Types as A
1212
import Data.Default (def)
1313
import qualified Data.Dependent.Map as DMap
1414
import qualified Data.Dependent.Sum as DSum
15-
import Data.List (nub)
15+
import Data.List.Extra (nubOrd)
1616
import Data.String (IsString (fromString))
1717
import qualified Data.Text as T
1818
import Ide.Plugin.Config
@@ -62,7 +62,7 @@ pluginsToDefaultConfig IdePlugins {..} =
6262
-- }
6363
--
6464
genericDefaultConfig =
65-
let x = ["diagnosticsOn" A..= True | configHasDiagnostics] <> nub (mconcat (handlersToGenericDefaultConfig <$> handlers))
65+
let x = ["diagnosticsOn" A..= True | configHasDiagnostics] <> nubOrd (mconcat (handlersToGenericDefaultConfig <$> handlers))
6666
in case x of
6767
-- if the plugin has only one capability, we produce globalOn instead of the specific one;
6868
-- otherwise we don't produce globalOn at all
@@ -106,7 +106,7 @@ pluginsToVSCodeExtensionSchema IdePlugins {..} = A.object $ mconcat $ singlePlug
106106
genericSchema =
107107
let x =
108108
[toKey' "diagnosticsOn" A..= schemaEntry "diagnostics" | configHasDiagnostics]
109-
<> nub (mconcat (handlersToGenericSchema <$> handlers))
109+
<> nubOrd (mconcat (handlersToGenericSchema <$> handlers))
110110
in case x of
111111
-- If the plugin has only one capability, we produce globalOn instead of the specific one;
112112
-- otherwise we don't produce globalOn at all

plugins/hls-alternate-number-format-plugin/hls-alternate-number-format-plugin.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,7 @@ library
3131
aeson
3232
, base >=4.12 && < 5
3333
, containers
34+
, extra
3435
, ghcide ^>= 1.8
3536
, ghc-boot-th
3637
, hls-graph

plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/Conversion.hs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ module Ide.Plugin.Conversion (
2323

2424
import Data.Char (toUpper)
2525
import Data.List (delete)
26+
import Data.List.Extra (upper, enumerate)
2627
import Data.Maybe (mapMaybe)
2728
import Data.Ratio (denominator, numerator)
2829
import Data.Text (Text)
@@ -108,10 +109,10 @@ filterFracFormats = mapMaybe getFracFormat
108109
getFracFormat _ = Nothing
109110

110111
intFormats :: [IntFormatType]
111-
intFormats = [minBound .. maxBound]
112+
intFormats = enumerate
112113

113114
fracFormats :: [FracFormatType]
114-
fracFormats = [minBound .. maxBound]
115+
fracFormats = enumerate
115116

116117
-- | Regex to match a Haskell Hex Literal
117118
hexRegex :: Text
@@ -157,8 +158,8 @@ sourceToFormatType srcText
157158

158159
toBase :: (Num a, Ord a) => (a -> ShowS) -> String -> a -> String
159160
toBase conv header n
160-
| n < 0 = '-' : header <> map toUpper (conv (abs n) "")
161-
| otherwise = header <> map toUpper (conv n "")
161+
| n < 0 = '-' : header <> upper (conv (abs n) "")
162+
| otherwise = header <> upper (conv n "")
162163

163164
toOctal :: (Integral a, Show a) => a -> String
164165
toOctal = toBase showOct "0o"

plugins/hls-code-range-plugin/src/Ide/Plugin/CodeRange.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@ import Control.Monad.IO.Class (liftIO)
1919
import Control.Monad.Trans.Maybe (MaybeT (MaybeT),
2020
maybeToExceptT)
2121
import Data.Either.Extra (maybeToEither)
22+
import Data.List.Extra (drop1)
2223
import Data.Maybe (fromMaybe)
2324
import Data.Vector (Vector)
2425
import qualified Data.Vector as V
@@ -206,7 +207,7 @@ findPosition pos root = go Nothing root
206207
findFoldingRanges :: CodeRange -> [FoldingRange]
207208
findFoldingRanges codeRange =
208209
-- removing the first node because it folds the entire file
209-
drop 1 $ findFoldingRangesRec codeRange
210+
drop1 $ findFoldingRangesRec codeRange
210211

211212
findFoldingRangesRec :: CodeRange -> [FoldingRange]
212213
findFoldingRangesRec r@(CodeRange _ children _) =

plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -306,7 +306,7 @@ abbreviateImportTitle input =
306306
oneLineText = T.unwords $ T.lines input
307307
-- Now, split at the max columns, leaving space for the summary text we're going to add
308308
-- (conservatively assuming we won't need to print a number larger than 100)
309-
(prefix, suffix) = T.splitAt (maxColumns - (T.length (summaryText 100))) oneLineText
309+
(prefix, suffix) = T.splitAt (maxColumns - T.length (summaryText 100)) oneLineText
310310
-- We also want to truncate the last item so we get a "clean" break, rather than half way through
311311
-- something. The conditional here is just because 'breakOnEnd' doesn't give us quite the right thing
312312
-- if there are actually no commas.

shake-bench/src/Development/Benchmark/Rules.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -690,7 +690,7 @@ plotDiagram includeFailed t@Diagram {traceMetric, runLogs} out = do
690690
]
691691
]
692692
return (lplot E.& E.plot_lines_style . E.line_width E.*~ 2)
693-
case (runFirstReponse rl) of
693+
case runFirstReponse rl of
694694
Just t -> E.plot $ pure $
695695
E.vlinePlot ("First build: " ++ runVersion rl) (E.defaultPlotLineStyle E.& E.line_color E..~ c) t
696696
_ -> pure ()

0 commit comments

Comments
 (0)