Skip to content

Commit b378de2

Browse files
andys8pepeiborra
andauthored
Solve formatting issues (stylish-haskell, pre-commit CI) (#3171)
* Solve formatting issues * stylish-haskell parse errors solved (partially) * Env: Changing order (import) * Plugins: Dangling `$` Co-authored-by: Pepe Iborra <[email protected]>
1 parent a13e1b3 commit b378de2

File tree

18 files changed

+74
-77
lines changed

18 files changed

+74
-77
lines changed

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

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
22
-- SPDX-License-Identifier: Apache-2.0
3-
{-# LANGUAGE CPP #-}
3+
{-# LANGUAGE CPP #-}
44

55
module Development.IDE.Core.Preprocessor
66
( preprocessor
@@ -30,8 +30,8 @@ import qualified GHC.LanguageExtensions as LangExt
3030
import System.FilePath
3131
import System.IO.Extra
3232
#if MIN_VERSION_ghc(9,3,0)
33-
import GHC.Utils.Logger (LogFlags(..))
34-
import GHC.Utils.Outputable (renderWithContext)
33+
import GHC.Utils.Logger (LogFlags (..))
34+
import GHC.Utils.Outputable (renderWithContext)
3535
#endif
3636

3737
-- | Given a file and some contents, apply any necessary preprocessors,

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

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -130,11 +130,10 @@ import Development.IDE.GHC.Compat (NameCache,
130130
NameCacheUpdater (..),
131131
initNameCache,
132132
knownKeyNames,
133+
mkSplitUniqSupply)
133134
#if !MIN_VERSION_ghc(9,3,0)
134-
upNameCache,
135+
import Development.IDE.GHC.Compat (upNameCache)
135136
#endif
136-
mkSplitUniqSupply
137-
)
138137
import Development.IDE.GHC.Orphans ()
139138
import Development.IDE.Graph hiding (ShakeValue)
140139
import qualified Development.IDE.Graph as Shake

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,7 @@ import DynFlags
3535
#endif
3636
#endif
3737
#if MIN_VERSION_ghc(9,3,0)
38-
import qualified GHC.Driver.Pipeline.Execute as Pipeline
38+
import qualified GHC.Driver.Pipeline.Execute as Pipeline
3939
#endif
4040

4141
addOptP :: String -> DynFlags -> DynFlags

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

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -91,11 +91,6 @@ import HscTypes as Env
9191
import Module
9292
#endif
9393

94-
#if MIN_VERSION_ghc(9,3,0)
95-
hsc_EPS :: HscEnv -> UnitEnv
96-
hsc_EPS = hsc_unit_env
97-
#endif
98-
9994
#if MIN_VERSION_ghc(9,0,0)
10095
#if !MIN_VERSION_ghc(9,2,0)
10196
import qualified Data.Set as Set
@@ -105,6 +100,11 @@ import qualified Data.Set as Set
105100
import Data.IORef
106101
#endif
107102

103+
#if MIN_VERSION_ghc(9,3,0)
104+
hsc_EPS :: HscEnv -> UnitEnv
105+
hsc_EPS = hsc_unit_env
106+
#endif
107+
108108
#if !MIN_VERSION_ghc(9,2,0)
109109
type UnitEnv = ()
110110
newtype Logger = Logger { log_action :: LogAction }

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ import DynFlags
2525
import Outputable (queryQual)
2626
#endif
2727
#if MIN_VERSION_ghc(9,3,0)
28-
import GHC.Types.Error
28+
import GHC.Types.Error
2929
#endif
3030

3131
putLogHook :: Logger -> HscEnv -> HscEnv

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

Lines changed: 6 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -24,12 +24,12 @@ import qualified GHC.Driver.Env as Env
2424
import GHC.Driver.Plugins (Plugin (..),
2525
PluginWithArgs (..),
2626
StaticPlugin (..),
27+
defaultPlugin, withPlugins)
2728
#if MIN_VERSION_ghc(9,3,0)
28-
staticPlugins,
29-
ParsedResult(..),
30-
PsMessages(..),
29+
import GHC.Driver.Plugins (ParsedResult (..),
30+
PsMessages (..),
31+
staticPlugins)
3132
#endif
32-
defaultPlugin, withPlugins)
3333
import qualified GHC.Runtime.Loader as Loader
3434
#elif MIN_VERSION_ghc(8,8,0)
3535
import qualified DynamicLoading as Loader
@@ -48,11 +48,10 @@ applyPluginsParsedResultAction env dflags ms hpm_annotations parsed = do
4848
-- Apply parsedResultAction of plugins
4949
let applyPluginAction p opts = parsedResultAction p opts ms
5050
#if MIN_VERSION_ghc(9,3,0)
51-
fmap (hpm_module . parsedResultModule) $
51+
fmap (hpm_module . parsedResultModule) $ runHsc env $ withPlugins
5252
#else
53-
fmap hpm_module $
53+
fmap hpm_module $ runHsc env $ withPlugins
5454
#endif
55-
runHsc env $ withPlugins
5655
#if MIN_VERSION_ghc(9,3,0)
5756
(Env.hsc_plugins env)
5857
#elif MIN_VERSION_ghc(9,2,0)

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

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -52,11 +52,11 @@ module Development.IDE.GHC.Compat.Units (
5252
showSDocForUser',
5353
) where
5454

55-
import qualified Data.List.NonEmpty as NE
56-
import qualified Data.Map.Strict as Map
57-
import Control.Monad
55+
import Control.Monad
56+
import qualified Data.List.NonEmpty as NE
57+
import qualified Data.Map.Strict as Map
5858
#if MIN_VERSION_ghc(9,3,0)
59-
import GHC.Unit.Home.ModInfo
59+
import GHC.Unit.Home.ModInfo
6060
#endif
6161
#if MIN_VERSION_ghc(9,0,0)
6262
#if MIN_VERSION_ghc(9,2,0)

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

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ import GHC.ByteCode.Types
4444
import ByteCodeTypes
4545
#endif
4646
#if MIN_VERSION_ghc(9,3,0)
47-
import GHC.Types.PkgQual
47+
import GHC.Types.PkgQual
4848
#endif
4949

5050
-- Orphan instances for types from the GHC API.
@@ -217,8 +217,8 @@ instance NFData HomeModInfo where
217217

218218
#if MIN_VERSION_ghc(9,3,0)
219219
instance NFData PkgQual where
220-
rnf NoPkgQual = ()
221-
rnf (ThisPkg uid) = rnf uid
220+
rnf NoPkgQual = ()
221+
rnf (ThisPkg uid) = rnf uid
222222
rnf (OtherPkg uid) = rnf uid
223223

224224
instance NFData UnitId where

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

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
22
-- SPDX-License-Identifier: Apache-2.0
3+
{-# LANGUAGE CPP #-}
34
{-# LANGUAGE ExplicitNamespaces #-}
4-
{-# LANGUAGE CPP #-}
55

66
module Development.IDE.GHC.Warnings(withWarnings) where
77

@@ -49,8 +49,8 @@ attachReason Nothing d = d
4949
attachReason (Just wr) d = d{_code = InR <$> showReason wr}
5050
where
5151
showReason = \case
52-
WarningWithFlag flag -> showFlag flag
53-
_ -> Nothing
52+
WarningWithFlag flag -> showFlag flag
53+
_ -> Nothing
5454
#else
5555
attachReason :: WarnReason -> Diagnostic -> Diagnostic
5656
attachReason wr d = d{_code = InR <$> showReason wr}

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

Lines changed: 23 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -8,46 +8,45 @@ module Development.IDE.Plugin.Completions
88
, ghcideCompletionsPluginPriority
99
) where
1010

11-
import Control.Concurrent.Async (concurrently)
12-
import Control.Concurrent.STM.Stats (readTVarIO)
11+
import Control.Concurrent.Async (concurrently)
12+
import Control.Concurrent.STM.Stats (readTVarIO)
1313
import Control.Monad.Extra
1414
import Control.Monad.IO.Class
1515
import Control.Monad.Trans.Maybe
1616
import Data.Aeson
17-
import qualified Data.HashMap.Strict as Map
18-
import qualified Data.HashSet as Set
19-
import Data.List (find)
17+
import qualified Data.HashMap.Strict as Map
18+
import qualified Data.HashSet as Set
19+
import Data.List (find)
2020
import Data.Maybe
21-
import qualified Data.Text as T
21+
import qualified Data.Text as T
2222
import Development.IDE.Core.PositionMapping
2323
import Development.IDE.Core.RuleTypes
24-
import Development.IDE.Core.Service hiding (Log,
25-
LogShake)
26-
import Development.IDE.Core.Shake hiding (Log)
27-
import qualified Development.IDE.Core.Shake as Shake
24+
import Development.IDE.Core.Service hiding (Log, LogShake)
25+
import Development.IDE.Core.Shake hiding (Log)
26+
import qualified Development.IDE.Core.Shake as Shake
2827
import Development.IDE.GHC.Compat
29-
import Development.IDE.GHC.Error (rangeToSrcSpan)
30-
import Development.IDE.GHC.Util (printOutputable)
28+
import Development.IDE.GHC.Error (rangeToSrcSpan)
29+
import Development.IDE.GHC.Util (printOutputable)
3130
import Development.IDE.Graph
3231
import Development.IDE.Plugin.Completions.Logic
3332
import Development.IDE.Plugin.Completions.Types
3433
import Development.IDE.Types.Exports
35-
import Development.IDE.Types.HscEnvEq (HscEnvEq (envPackageExports),
36-
hscEnv)
37-
import qualified Development.IDE.Types.KnownTargets as KT
34+
import Development.IDE.Types.HscEnvEq (HscEnvEq (envPackageExports),
35+
hscEnv)
36+
import qualified Development.IDE.Types.KnownTargets as KT
3837
import Development.IDE.Types.Location
39-
import Development.IDE.Types.Logger (Pretty (pretty),
40-
Recorder,
41-
WithPriority,
42-
cmapWithPrio)
43-
import GHC.Exts (fromList, toList)
44-
import Ide.Plugin.Config (Config)
38+
import Development.IDE.Types.Logger (Pretty (pretty),
39+
Recorder,
40+
WithPriority,
41+
cmapWithPrio)
42+
import GHC.Exts (fromList, toList)
43+
import Ide.Plugin.Config (Config)
4544
import Ide.Types
46-
import qualified Language.LSP.Server as LSP
45+
import qualified Language.LSP.Server as LSP
4746
import Language.LSP.Types
48-
import qualified Language.LSP.VFS as VFS
47+
import qualified Language.LSP.VFS as VFS
4948
import Numeric.Natural
50-
import Text.Fuzzy.Parallel (Scored (..))
49+
import Text.Fuzzy.Parallel (Scored (..))
5150

5251
data Log = LogShake Shake.Log deriving Show
5352

0 commit comments

Comments
 (0)