Skip to content

Commit 944794e

Browse files
committed
warnings and hlint
1 parent 7c667c8 commit 944794e

File tree

42 files changed

+38
-66
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

42 files changed

+38
-66
lines changed

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -105,7 +105,7 @@ kick = do
105105
-- Update the exports map for non FOIs
106106
-- We can skip this if checkProject is True, assuming they never change under our feet.
107107
IdeOptions{ optCheckProject = doCheckProject } <- getIdeOptions
108-
checkProject <- liftIO $ doCheckProject
108+
checkProject <- liftIO doCheckProject
109109
ifaces <- if checkProject then return Nothing else runMaybeT $ do
110110
deps <- MaybeT $ sequence <$> uses GetDependencies files
111111
hiResults <- lift $ uses GetModIface (nubOrd $ foldMap transitiveModuleDeps deps)

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

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
{-# LANGUAGE CPP #-}
2-
{-# LANGUAGE DataKinds #-}
32
#include "ghc-api-version.h"
43
module Development.IDE.Core.Tracing
54
( otTracedHandler

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

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2,10 +2,6 @@
22
-- SPDX-License-Identifier: Apache-2.0
33
{-# LANGUAGE RankNTypes #-}
44
{-# LANGUAGE GADTs #-}
5-
{-# LANGUAGE TypeOperators #-}
6-
{-# LANGUAGE ScopedTypeVariables #-}
7-
{-# LANGUAGE DataKinds #-}
8-
{-# LANGUAGE ViewPatterns #-}
95

106
-- | Display information on hover.
117
module Development.IDE.LSP.HoverDefinition

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

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -4,9 +4,7 @@
44
{-# LANGUAGE ExistentialQuantification #-}
55
{-# LANGUAGE GADTs #-}
66
{-# LANGUAGE PolyKinds #-}
7-
{-# LANGUAGE DataKinds #-}
8-
{-# LANGUAGE RankNTypes #-}
9-
{-# LANGUAGE ScopedTypeVariables #-}
7+
{-# LANGUAGE RankNTypes #-}
108

119
-- WARNING: A copy of DA.Daml.LanguageServer, try to keep them in sync
1210
-- This version removes the daml: handling
@@ -142,7 +140,7 @@ runLanguageServer options onConfigurationChange userHandlers getIdeState = do
142140
liftIO $ logInfo (ideLogger ide) $ T.pack $ "Registering ide configuration: " <> show initConfig
143141
liftIO $ registerIdeConfiguration (shakeExtras ide) initConfig
144142

145-
_ <- flip forkFinally (const $ exitClientMsg) $ forever $ do
143+
_ <- flip forkFinally (const exitClientMsg) $ forever $ do
146144
msg <- readChan clientMsgChan
147145
-- We dispatch notifications synchronously and requests asynchronously
148146
-- This is to ensure that all file edits and config changes are applied before a request is handled

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

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
{-# LANGUAGE CPP #-}
22

3-
{-# LANGUAGE TypeOperators #-}
43
{-# LANGUAGE RankNTypes #-}
54
{-# LANGUAGE GADTs #-}
65
{-# LANGUAGE DuplicateRecordFields #-}

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

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -6,9 +6,14 @@
66
{-# LANGUAGE DuplicateRecordFields #-}
77
{-# LANGUAGE RankNTypes #-}
88
{-# LANGUAGE KindSignatures #-}
9-
{-# LANGUAGE DataKinds #-}
109
{-# LANGUAGE GADTs #-}
11-
module Development.IDE.LSP.Server where
10+
module Development.IDE.LSP.Server
11+
( ReactorMessage(..)
12+
, ReactorChan
13+
, ServerM
14+
, requestHandler
15+
, notificationHandler
16+
) where
1217

1318
import Language.LSP.Server (LspM, Handlers)
1419
import Language.LSP.Types

ghcide/src/Development/IDE/Plugin.hs

Lines changed: 1 addition & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,4 @@
1-
{-# LANGUAGE RankNTypes #-}
2-
{-# LANGUAGE GADTs #-}
3-
{-# LANGUAGE TypeOperators #-}
4-
{-# LANGUAGE ScopedTypeVariables #-}
5-
module Development.IDE.Plugin where
1+
module Development.IDE.Plugin ( Plugin(..) ) where
62

73
import Data.Default
84
import Development.Shake

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

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,8 +2,6 @@
22
-- SPDX-License-Identifier: Apache-2.0
33

44
{-# LANGUAGE DuplicateRecordFields #-}
5-
{-# LANGUAGE DataKinds #-}
6-
{-# LANGUAGE TypeOperators #-}
75
{-# LANGUAGE CPP #-}
86
{-# LANGUAGE RankNTypes #-}
97
{-# LANGUAGE GADTs #-}

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

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
{-# LANGUAGE CPP #-}
2-
{-# LANGUAGE DataKinds #-}
32
{-# LANGUAGE RankNTypes #-}
43
{-# LANGUAGE TypeFamilies #-}
54
#include "ghc-api-version.h"

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

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,4 @@
11
{-# LANGUAGE PolyKinds #-}
2-
{-# LANGUAGE KindSignatures #-}
3-
{-# LANGUAGE DataKinds #-}
42
{-# LANGUAGE GADTs #-}
53

64
module Development.IDE.Plugin.HLS
@@ -35,6 +33,7 @@ import Data.Dependent.Sum
3533
import Data.List.NonEmpty (nonEmpty,NonEmpty,toList)
3634
import UnliftIO (MonadUnliftIO)
3735
import Data.String
36+
import Data.Bifunctor
3837

3938
-- ---------------------------------------------------------------------
4039
--
@@ -50,7 +49,7 @@ asGhcIdePlugin mp =
5049

5150
mkPlugin :: ([(PluginId, b)] -> Plugin Config) -> (PluginDescriptor IdeState -> b) -> Plugin Config
5251
mkPlugin maker selector =
53-
case map (\(pid, p) -> (pid, selector p)) ls of
52+
case map (second selector) ls of
5453
-- If there are no plugins that provide a descriptor, use mempty to
5554
-- create the plugin – otherwise we we end up declaring handlers for
5655
-- capabilities that there are no plugins for
@@ -173,7 +172,7 @@ combineErrors xs = ResponseError InternalError (T.pack (show xs)) Nothing
173172

174173
-- | Combine the 'PluginHandler' for all plugins
175174
newtype IdeHandler (m :: J.Method FromClient Request)
176-
= IdeHandler [(PluginId,(IdeState -> MessageParams m -> LSP.LspM Config (NonEmpty (Either ResponseError (ResponseResult m)))))]
175+
= IdeHandler [(PluginId,IdeState -> MessageParams m -> LSP.LspM Config (NonEmpty (Either ResponseError (ResponseResult m))))]
177176

178177
-- | Combine the 'PluginHandlers' for all plugins
179178
newtype IdeHandlers = IdeHandlers (DMap IdeMethod IdeHandler)

0 commit comments

Comments
 (0)