Skip to content

Commit 7215d80

Browse files
dylan-thinnesJaro Reinders
authored andcommitted
Fix all stylish-haskell errors triggering
1 parent aaf5736 commit 7215d80

File tree

12 files changed

+141
-131
lines changed

12 files changed

+141
-131
lines changed

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -40,12 +40,12 @@ import Development.IDE.Import.FindImports (ArtifactsLocation
4040
import Development.IDE.Spans.Common
4141
import Development.IDE.Spans.LocalBindings
4242
import Development.IDE.Types.Diagnostics
43+
import GHC.Driver.Errors.Types (WarningMessages)
4344
import GHC.Serialized (Serialized)
4445
import Ide.Logger (Pretty (..),
4546
viaShow)
4647
import Language.LSP.Protocol.Types (Int32,
4748
NormalizedFilePath)
48-
import GHC.Driver.Errors.Types (WarningMessages)
4949

5050
data LinkableType = ObjectLinkable | BCOLinkable
5151
deriving (Eq,Ord,Show, Generic)

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -83,7 +83,7 @@ import Control.Concurrent.STM.Stats (atomicallyNamed)
8383
import Control.Concurrent.Strict
8484
import Control.DeepSeq
8585
import Control.Exception.Extra hiding (bracket_)
86-
import Control.Lens ((&), (?~), (%~), over)
86+
import Control.Lens (over, (%~), (&), (?~))
8787
import Control.Monad.Extra
8888
import Control.Monad.IO.Class
8989
import Control.Monad.Reader

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

Lines changed: 31 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -6,42 +6,43 @@
66
-- MR to add this function: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12891
77
-- ============================================================================
88

9-
{-# LANGUAGE CPP #-}
9+
{-# LANGUAGE CPP #-}
1010

1111
module Development.IDE.GHC.Compat.Driver
1212
( hscTypecheckRenameWithDiagnostics
1313
) where
1414

15-
import GHC.Driver.Main
16-
import GHC.Driver.Session
17-
import GHC.Driver.Env
18-
import GHC.Driver.Errors.Types
19-
import GHC.Hs
20-
import GHC.Hs.Dump
21-
import GHC.Iface.Ext.Ast ( mkHieFile )
22-
import GHC.Iface.Ext.Types ( getAsts, hie_asts, hie_module )
23-
import GHC.Iface.Ext.Binary ( readHieFile, writeHieFile , hie_file_result)
24-
import GHC.Iface.Ext.Debug ( diffFile, validateScopes )
25-
import GHC.Core
26-
import GHC.Tc.Module
27-
import GHC.Tc.Utils.Monad
28-
import GHC.Unit
29-
import GHC.Unit.Module.ModDetails
30-
import GHC.Unit.Module.ModIface
31-
import GHC.Unit.Module.ModSummary
32-
import GHC.Types.SourceFile
33-
import GHC.Types.SrcLoc
34-
import GHC.Utils.Panic.Plain
35-
import GHC.Utils.Error
36-
import GHC.Utils.Outputable
37-
import GHC.Utils.Logger
38-
import GHC.Data.FastString
39-
import GHC.Data.Maybe
40-
import Control.Monad
15+
import Control.Monad
16+
import GHC.Core
17+
import GHC.Data.FastString
18+
import GHC.Data.Maybe
19+
import GHC.Driver.Env
20+
import GHC.Driver.Errors.Types
21+
import GHC.Driver.Main
22+
import GHC.Driver.Session
23+
import GHC.Hs
24+
import GHC.Hs.Dump
25+
import GHC.Iface.Ext.Ast (mkHieFile)
26+
import GHC.Iface.Ext.Binary (hie_file_result, readHieFile,
27+
writeHieFile)
28+
import GHC.Iface.Ext.Debug (diffFile, validateScopes)
29+
import GHC.Iface.Ext.Types (getAsts, hie_asts, hie_module)
30+
import GHC.Tc.Module
31+
import GHC.Tc.Utils.Monad
32+
import GHC.Types.SourceFile
33+
import GHC.Types.SrcLoc
34+
import GHC.Unit
35+
import GHC.Unit.Module.ModDetails
36+
import GHC.Unit.Module.ModIface
37+
import GHC.Unit.Module.ModSummary
38+
import GHC.Utils.Error
39+
import GHC.Utils.Logger
40+
import GHC.Utils.Outputable
41+
import GHC.Utils.Panic.Plain
4142

4243
#if !MIN_VERSION_ghc(9,6,1)
43-
import Development.IDE.GHC.Compat.Core (hscTypecheckRename)
44-
import GHC.Utils.Error (emptyMessages)
44+
import Development.IDE.GHC.Compat.Core (hscTypecheckRename)
45+
import GHC.Utils.Error (emptyMessages)
4546
#endif
4647

4748
hscTypecheckRenameWithDiagnostics :: HscEnv -> ModSummary -> HsParsedModule
@@ -78,7 +79,7 @@ hsc_typecheck keep_rn mod_summary mb_rdr_module = do
7879
else
7980
do hpm <- case mb_rdr_module of
8081
Just hpm -> return hpm
81-
Nothing -> hscParse' mod_summary
82+
Nothing -> hscParse' mod_summary
8283
tc_result0 <- tcRnModule' mod_summary keep_rn' hpm
8384
if hsc_src == HsigFile
8485
then do (iface, _) <- liftIO $ hscSimpleIface hsc_env Nothing tc_result0 mod_summary

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

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
{-# LANGUAGE CPP #-}
1+
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE DisambiguateRecordFields #-}
33
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
44
-- SPDX-License-Identifier: Apache-2.0
@@ -41,10 +41,11 @@ import Data.Maybe
4141
import Data.String (fromString)
4242
import qualified Data.Text as T
4343
import Data.Tuple.Extra (uncurry3)
44-
import Development.IDE.GHC.Compat (MsgEnvelope,
45-
errMsgSeverity, errMsgSpan, errMsgDiagnostic,
44+
import Development.IDE.GHC.Compat (GhcMessage, MsgEnvelope,
45+
errMsgDiagnostic,
46+
errMsgSeverity, errMsgSpan,
4647
formatErrorWithQual,
47-
srcErrorMessages, GhcMessage)
48+
srcErrorMessages)
4849
import qualified Development.IDE.GHC.Compat as Compat
4950
import qualified Development.IDE.GHC.Compat.Util as Compat
5051
import Development.IDE.GHC.Orphans ()

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -6,12 +6,12 @@
66
module Development.IDE.GHC.Warnings(withWarnings) where
77

88
import Control.Concurrent.Strict
9-
import Control.Lens (over)
9+
import Control.Lens (over)
1010
import qualified Data.Text as T
1111

1212
import Development.IDE.GHC.Compat
13-
import Development.IDE.Types.Diagnostics
1413
import Development.IDE.GHC.Error
14+
import Development.IDE.Types.Diagnostics
1515

1616
{-
1717
NOTE on withWarnings and its dangers

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

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -26,11 +26,12 @@ import Data.List (find)
2626
import qualified Data.Map as Map
2727
import Data.Maybe (catMaybes, maybeToList)
2828
import qualified Data.Text as T
29-
import Development.IDE (GhcSession (..),
29+
import Development.IDE (FileDiagnostic (..),
30+
GhcSession (..),
3031
HscEnvEq (hscEnv),
3132
RuleResult, Rules, Uri,
3233
define, srcSpanToRange,
33-
usePropertyAction, FileDiagnostic (..))
34+
usePropertyAction)
3435
import Development.IDE.Core.Compile (TcModuleResult (..))
3536
import Development.IDE.Core.PluginUtils
3637
import Development.IDE.Core.PositionMapping (PositionMapping,

ghcide/src/Development/IDE/Types/Diagnostics.hs

Lines changed: 25 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,9 @@
11
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
22
-- SPDX-License-Identifier: Apache-2.0
33

4-
{-# LANGUAGE DeriveGeneric #-}
4+
{-# LANGUAGE CPP #-}
5+
{-# LANGUAGE DeriveGeneric #-}
56
{-# LANGUAGE TemplateHaskell #-}
6-
{-# LANGUAGE CPP #-}
77

88
module Development.IDE.Types.Diagnostics (
99
LSP.Diagnostic(..),
@@ -28,20 +28,22 @@ module Development.IDE.Types.Diagnostics (
2828

2929
import Control.DeepSeq
3030
import Control.Lens
31-
import qualified Data.Aeson as JSON
32-
import qualified Data.Aeson.Lens as JSON
31+
import qualified Data.Aeson as JSON
32+
import qualified Data.Aeson.Lens as JSON
3333
import Data.ByteString (ByteString)
3434
import Data.List
3535
import Data.Maybe as Maybe
3636
import qualified Data.Text as T
37-
import Development.IDE.GHC.Compat (GhcMessage, MsgEnvelope, WarningFlag, wWarningFlags, flagSpecFlag, flagSpecName)
37+
import Development.IDE.GHC.Compat (GhcMessage, MsgEnvelope,
38+
WarningFlag, flagSpecFlag,
39+
flagSpecName, wWarningFlags)
3840
import Development.IDE.Types.Location
3941
import GHC.Generics
40-
import GHC.Types.Error ( errMsgDiagnostic, DiagnosticReason(..), diagnosticReason
41-
#if MIN_VERSION_ghc(9,6,1)
42-
, diagnosticCode, DiagnosticCode (..)
43-
#endif
44-
)
42+
import GHC.Types.Error (DiagnosticCode (..),
43+
DiagnosticReason (..),
44+
diagnosticCode,
45+
diagnosticReason,
46+
errMsgDiagnostic)
4547
import Language.LSP.Diagnostics
4648
import Language.LSP.Protocol.Lens (data_)
4749
import Language.LSP.Protocol.Types as LSP
@@ -80,7 +82,7 @@ ideErrorFromLspDiag lspDiag fdFilePath origMsg =
8082
let fdShouldShowDiagnostic = ShowDiag
8183
fdStructuredMessage =
8284
case origMsg of
83-
Nothing -> NoStructuredMessage
85+
Nothing -> NoStructuredMessage
8486
Just msg -> SomeStructuredMessage msg
8587
fdLspDiagnostic = (attachReason (fmap (diagnosticReason . errMsgDiagnostic) origMsg) lspDiag)
8688
#if MIN_VERSION_ghc(9,6,1)
@@ -161,22 +163,22 @@ data StructuredMessage
161163
deriving (Generic)
162164

163165
instance Show StructuredMessage where
164-
show NoStructuredMessage = "NoStructuredMessage"
166+
show NoStructuredMessage = "NoStructuredMessage"
165167
show SomeStructuredMessage {} = "SomeStructuredMessage"
166168

167169
instance Eq StructuredMessage where
168-
(==) NoStructuredMessage NoStructuredMessage = True
170+
(==) NoStructuredMessage NoStructuredMessage = True
169171
(==) SomeStructuredMessage {} SomeStructuredMessage {} = True
170-
(==) _ _ = False
172+
(==) _ _ = False
171173

172174
instance Ord StructuredMessage where
173-
compare NoStructuredMessage NoStructuredMessage = EQ
175+
compare NoStructuredMessage NoStructuredMessage = EQ
174176
compare SomeStructuredMessage {} SomeStructuredMessage {} = EQ
175-
compare NoStructuredMessage SomeStructuredMessage {} = GT
176-
compare SomeStructuredMessage {} NoStructuredMessage = LT
177+
compare NoStructuredMessage SomeStructuredMessage {} = GT
178+
compare SomeStructuredMessage {} NoStructuredMessage = LT
177179

178180
instance NFData StructuredMessage where
179-
rnf NoStructuredMessage = ()
181+
rnf NoStructuredMessage = ()
180182
rnf SomeStructuredMessage {} = ()
181183

182184
-- | Human readable diagnostics for a specific file.
@@ -189,14 +191,14 @@ instance NFData StructuredMessage where
189191
-- StructuredMessage.
190192
--
191193
data FileDiagnostic = FileDiagnostic
192-
{ fdFilePath :: NormalizedFilePath
194+
{ fdFilePath :: NormalizedFilePath
193195
, fdShouldShowDiagnostic :: ShowDiagnostic
194-
, fdLspDiagnostic :: Diagnostic
196+
, fdLspDiagnostic :: Diagnostic
195197
-- | The optional GhcMessage inside of this StructuredMessage is ignored for
196198
-- Eq, Ord, Show, and NFData instances. This is fine because this field
197199
-- should only ever be metadata and should never be used to distinguish
198200
-- between FileDiagnostics.
199-
, fdStructuredMessage :: StructuredMessage
201+
, fdStructuredMessage :: StructuredMessage
200202
}
201203
deriving (Eq, Ord, Show, Generic)
202204

@@ -233,8 +235,8 @@ prettyDiagnostic FileDiagnostic { fdFilePath, fdShouldShowDiagnostic, fdLspDiagn
233235
, slabel_ "Severity:" $ pretty $ show sev
234236
, slabel_ "Code: " $ case _code of
235237
Just (InR text) -> pretty text
236-
Just (InL i) -> pretty i
237-
Nothing -> "<none>"
238+
Just (InL i) -> pretty i
239+
Nothing -> "<none>"
238240
, slabel_ "Message: "
239241
$ case sev of
240242
LSP.DiagnosticSeverity_Error -> annotate $ color Red

ghcide/src/Text/Fuzzy/Parallel.hs

Lines changed: 10 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -89,8 +89,7 @@ simpleFilter :: Int -- ^ Chunk size. 1000 works well.
8989
-> T.Text -- ^ Pattern to look for.
9090
-> [T.Text] -- ^ List of texts to check.
9191
-> [Scored T.Text] -- ^ The ones that match.
92-
simpleFilter chunk maxRes pattern xs =
93-
filter chunk maxRes pattern xs id
92+
simpleFilter chunk maxRes pat xs = filter chunk maxRes pat xs id
9493

9594

9695
-- | The function to filter a list of values by fuzzy search on the text extracted from them,
@@ -104,15 +103,15 @@ filter' :: Int -- ^ Chunk size. 1000 works well.
104103
-- ^ Custom scoring function to use for calculating how close words are
105104
-- When the function returns Nothing, this means the values are incomparable.
106105
-> [Scored t] -- ^ The list of results, sorted, highest score first.
107-
filter' chunkSize maxRes pattern ts extract match' = partialSortByAscScore maxRes perfectScore (concat vss)
106+
filter' chunkSize maxRes pat ts extract match' = partialSortByAscScore maxRes perfectScore (concat vss)
108107
where
109108
-- Preserve case for the first character, make all others lowercase
110-
pattern' = case T.uncons pattern of
109+
pat' = case T.uncons pat of
111110
Just (c, rest) -> T.cons c (T.toLower rest)
112-
_ -> pattern
113-
vss = map (mapMaybe (\t -> flip Scored t <$> match' pattern' (extract t))) (chunkList chunkSize ts)
111+
_ -> pat
112+
vss = map (mapMaybe (\t -> flip Scored t <$> match' pat' (extract t))) (chunkList chunkSize ts)
114113
`using` parList (evalList rseq)
115-
perfectScore = fromMaybe (error $ T.unpack pattern) $ match' pattern' pattern'
114+
perfectScore = fromMaybe (error $ T.unpack pat) $ match' pat' pat'
116115

117116
-- | The function to filter a list of values by fuzzy search on the text extracted from them,
118117
-- using a custom matching function which determines how close words are.
@@ -122,8 +121,8 @@ filter :: Int -- ^ Chunk size. 1000 works well.
122121
-> [t] -- ^ The list of values containing the text to search in.
123122
-> (t -> T.Text) -- ^ The function to extract the text from the container.
124123
-> [Scored t] -- ^ The list of results, sorted, highest score first.
125-
filter chunkSize maxRes pattern ts extract =
126-
filter' chunkSize maxRes pattern ts extract match
124+
filter chunkSize maxRes pat ts extract =
125+
filter' chunkSize maxRes pat ts extract match
127126

128127
-- | Return all elements of the list that have a fuzzy match against the pattern,
129128
-- the closeness of the match is determined using the custom scoring match function that is passed.
@@ -136,8 +135,8 @@ simpleFilter' :: Int -- ^ Chunk size. 1000 works well.
136135
-> (T.Text -> T.Text -> Maybe Int)
137136
-- ^ Custom scoring function to use for calculating how close words are
138137
-> [Scored T.Text] -- ^ The ones that match.
139-
simpleFilter' chunk maxRes pattern xs match' =
140-
filter' chunk maxRes pattern xs id match'
138+
simpleFilter' chunk maxRes pat xs match' =
139+
filter' chunk maxRes pat xs id match'
141140
--------------------------------------------------------------------------------
142141

143142
chunkList :: Int -> [a] -> [[a]]

hls-test-utils/src/Development/IDE/Test/Diagnostic.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -36,8 +36,8 @@ requireDiagnostic actuals expected@(severity, cursor, expectedMsg, mbExpectedCod
3636

3737
codeMatches d =
3838
case (mbExpectedCode, _code d) of
39-
(Nothing, _) -> True
40-
(Just expectedCode, Nothing) -> False
39+
(Nothing, _) -> True
40+
(Just expectedCode, Nothing) -> False
4141
(Just expectedCode, Just actualCode) -> InR expectedCode == actualCode
4242

4343
hasTag :: Maybe DiagnosticTag -> Maybe [DiagnosticTag] -> Bool

plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal/Diagnostics.hs

Lines changed: 16 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -11,21 +11,22 @@ module Ide.Plugin.Cabal.Diagnostics
1111
)
1212
where
1313

14-
import Control.Lens ((.~), (&))
15-
import qualified Data.Text as T
16-
import Development.IDE (FileDiagnostic,
17-
ShowDiagnostic (ShowDiag))
18-
import Development.IDE.Types.Diagnostics (fdLspDiagnosticL, ideErrorWithSource)
19-
import Distribution.Fields (showPError, showPWarning)
20-
import qualified Distribution.Parsec as Syntax
21-
import Ide.PluginUtils (extendNextLine)
22-
import Language.LSP.Protocol.Types (Diagnostic (..),
23-
DiagnosticSeverity (..),
24-
NormalizedFilePath,
25-
Position (Position),
26-
Range (Range),
27-
fromNormalizedFilePath)
28-
import Language.LSP.Protocol.Lens (range)
14+
import Control.Lens ((&), (.~))
15+
import qualified Data.Text as T
16+
import Development.IDE (FileDiagnostic,
17+
ShowDiagnostic (ShowDiag))
18+
import Development.IDE.Types.Diagnostics (fdLspDiagnosticL,
19+
ideErrorWithSource)
20+
import Distribution.Fields (showPError, showPWarning)
21+
import qualified Distribution.Parsec as Syntax
22+
import Ide.PluginUtils (extendNextLine)
23+
import Language.LSP.Protocol.Lens (range)
24+
import Language.LSP.Protocol.Types (Diagnostic (..),
25+
DiagnosticSeverity (..),
26+
NormalizedFilePath,
27+
Position (Position),
28+
Range (Range),
29+
fromNormalizedFilePath)
2930

3031
-- | Produce a diagnostic for a fatal Cabal parser error.
3132
fatalParseErrorDiagnostic :: NormalizedFilePath -> T.Text -> FileDiagnostic

0 commit comments

Comments
 (0)