22{-# LANGUAGE LambdaCase #-}
33{-# LANGUAGE OverloadedStrings #-}
44{-# LANGUAGE TypeApplications #-}
5+ {-# LANGUAGE DataKinds #-}
6+ {-# LANGUAGE OverloadedLabels #-}
57
68module Ide.Plugin.Fourmolu (
79 descriptor ,
@@ -20,8 +22,8 @@ import Development.IDE hiding (pluginHandlers)
2022import Development.IDE.GHC.Compat as Compat hiding (Cpp )
2123import qualified Development.IDE.GHC.Compat.Util as S
2224import GHC.LanguageExtensions.Type (Extension (Cpp ))
23- import Ide.Plugin.Config ( formattingCLI )
24- import Ide.PluginUtils (makeDiffTextEdit )
25+ import Ide.Plugin.Properties
26+ import Ide.PluginUtils (makeDiffTextEdit , usePropertyLsp )
2527import Ide.Types
2628import Language.LSP.Server hiding (defaultConfig )
2729import Language.LSP.Types
@@ -32,22 +34,26 @@ import System.FilePath
3234import System.IO (stderr )
3335import System.Process.Text (readProcessWithExitCode )
3436
35- -- ---------------------------------------------------------------------
36-
3737descriptor :: PluginId -> PluginDescriptor IdeState
3838descriptor plId =
3939 (defaultPluginDescriptor plId)
40- { pluginHandlers = mkFormattingHandlers provider
40+ { pluginHandlers = mkFormattingHandlers $ provider plId
4141 }
4242
43- -- ---------------------------------------------------------------------
43+ properties :: Properties '[ 'PropertyKey " cli" 'TBoolean]
44+ properties =
45+ emptyProperties
46+ & defineBooleanProperty
47+ # cli
48+ " Call out to `fourmolu` executable, rather than using the bundled library"
49+ False
4450
45- provider :: FormattingHandler IdeState
46- provider ideState typ contents fp fo = withIndefiniteProgress title Cancellable $ do
51+ provider :: PluginId -> FormattingHandler IdeState
52+ provider plId ideState typ contents fp fo = withIndefiniteProgress title Cancellable $ do
4753 fileOpts <-
4854 maybe [] (convertDynFlags . hsc_dflags . hscEnv)
4955 <$> liftIO (runAction " Fourmolu" ideState $ use GhcSession fp)
50- useCLI <- formattingCLI <$> getConfig
56+ useCLI <- usePropertyLsp # cli plId properties
5157 if useCLI
5258 then liftIO
5359 . fmap (join . first (mkError . show ))
0 commit comments