44{-# LANGUAGE DuplicateRecordFields #-}
55{-# LANGUAGE FlexibleContexts #-}
66{-# LANGUAGE FlexibleInstances #-}
7+ {-# LANGUAGE OverloadedLabels #-}
78{-# LANGUAGE OverloadedStrings #-}
89{-# LANGUAGE PackageImports #-}
910{-# LANGUAGE ScopedTypeVariables #-}
@@ -33,9 +34,11 @@ import Data.Maybe
3334import qualified Data.Text as T
3435import qualified Data.Text.IO as T
3536import Data.Typeable
36- import Development.IDE
37+ import Development.IDE hiding
38+ (Error )
3739import Development.IDE.Core.Rules (defineNoFile ,
38- getParsedModuleWithComments )
40+ getParsedModuleWithComments ,
41+ usePropertyAction )
3942import Development.IDE.Core.Shake (getDiagnostics )
4043import Refact.Apply
4144
@@ -70,10 +73,13 @@ import Language.Haskell.GHC.ExactPrint.Types (Rigidity (.
7073#endif
7174
7275import Ide.Logger
73- import Ide.Plugin.Config
76+ import Ide.Plugin.Config hiding
77+ (Config )
78+ import Ide.Plugin.Properties
7479import Ide.PluginUtils
7580import Ide.Types
76- import Language.Haskell.HLint as Hlint
81+ import Language.Haskell.HLint as Hlint hiding
82+ (Error )
7783import Language.LSP.Server (ProgressCancellable (Cancellable ),
7884 sendRequest ,
7985 withIndefiniteProgress )
@@ -95,8 +101,11 @@ descriptor plId = (defaultPluginDescriptor plId)
95101 [ PluginCommand " applyOne" " Apply a single hint" applyOneCmd
96102 , PluginCommand " applyAll" " Apply all hints to the file" applyAllCmd
97103 ]
98- , pluginHandlers = mkPluginHandler STextDocumentCodeAction codeActionProvider
99- , pluginConfigDescriptor = defaultConfigDescriptor {configHasDiagnostics = True }
104+ , pluginHandlers = mkPluginHandler STextDocumentCodeAction codeActionProvider
105+ , pluginConfigDescriptor = defaultConfigDescriptor
106+ { configHasDiagnostics = True
107+ , configCustomConfig = mkCustomConfig properties
108+ }
100109 }
101110
102111-- This rule only exists for generating file diagnostics
@@ -126,7 +135,9 @@ rules plugin = do
126135 ideas <- if hlintOn' then getIdeas file else return (Right [] )
127136 return (diagnostics file ideas, Just () )
128137
129- getHlintSettingsRule (HlintEnabled [] )
138+ defineNoFile $ \ GetHlintSettings -> do
139+ (Config flags) <- getHlintConfig plugin
140+ liftIO $ argsSettings flags
130141
131142 action $ do
132143 files <- getFilesOfInterest
@@ -241,11 +252,6 @@ getExtensions pflags nfp = do
241252
242253-- ---------------------------------------------------------------------
243254
244- data HlintUsage
245- = HlintEnabled { cmdArgs :: [String ] }
246- | HlintDisabled
247- deriving Show
248-
249255data GetHlintSettings = GetHlintSettings
250256 deriving (Eq , Show , Typeable , Generic )
251257instance Hashable GetHlintSettings
@@ -259,15 +265,22 @@ instance Binary GetHlintSettings
259265
260266type instance RuleResult GetHlintSettings = (ParseFlags , [Classify ], Hint )
261267
262- getHlintSettingsRule :: HlintUsage -> Rules ()
263- getHlintSettingsRule usage =
264- defineNoFile $ \ GetHlintSettings ->
265- liftIO $ case usage of
266- HlintEnabled cmdArgs -> argsSettings cmdArgs
267- HlintDisabled -> fail " hlint configuration unspecified"
268-
269268-- ---------------------------------------------------------------------
270269
270+ newtype Config = Config [String ]
271+
272+ properties :: Properties '[ 'PropertyKey " flags" ('TArray String )]
273+ properties = emptyProperties
274+ & defineArrayProperty # flags
275+ " Flags used by hlint" []
276+
277+ -- | Get the plugin config
278+ getHlintConfig :: PluginId -> Action Config
279+ getHlintConfig pId =
280+ Config
281+ <$> usePropertyAction # flags pId properties
282+
283+ -- ---------------------------------------------------------------------
271284codeActionProvider :: PluginMethodHandler IdeState TextDocumentCodeAction
272285codeActionProvider ideState plId (CodeActionParams _ _ docId _ context) = Right . LSP. List . map InR <$> liftIO getCodeActions
273286 where
0 commit comments