11{-# LANGUAGE LambdaCase #-}
22{-# LANGUAGE OverloadedStrings #-}
3+ {-# LANGUAGE OverloadedLabels #-}
4+ {-# LANGUAGE DataKinds #-}
35
46module Ide.Plugin.CabalGild where
57
@@ -17,12 +19,13 @@ import System.Exit
1719import System.FilePath
1820import System.Process.ListLike
1921import qualified System.Process.Text as Process
22+ import Ide.Plugin.Properties
2023
2124data Log
2225 = LogProcessInvocationFailure Int T. Text
2326 | LogReadCreateProcessInfo [String ]
2427 | LogInvalidInvocationInfo
25- | LogFormatterBinNotFound
28+ | LogFormatterBinNotFound FilePath
2629 deriving (Show )
2730
2831instance Pretty Log where
@@ -35,30 +38,41 @@ instance Pretty Log where
3538 LogReadCreateProcessInfo args ->
3639 " Formatter invocation: cabal-gild " <+> pretty args
3740 LogInvalidInvocationInfo -> " Invocation of cabal-gild with range was called but is not supported."
38- LogFormatterBinNotFound -> " Couldn't find executable 'cabal-gild'"
41+ LogFormatterBinNotFound fp -> " Couldn't find formatter executable 'cabal-gild' at: " <+> pretty fp
3942
4043descriptor :: Recorder (WithPriority Log ) -> PluginId -> PluginDescriptor IdeState
4144descriptor recorder plId =
4245 (defaultCabalPluginDescriptor plId " Provides formatting of cabal files with cabal-gild" )
43- { pluginHandlers = mkFormattingHandlers (provider recorder)
46+ { pluginHandlers = mkFormattingHandlers (provider recorder plId)
47+ , pluginConfigDescriptor = defaultConfigDescriptor{configCustomConfig = mkCustomConfig properties}
4448 }
4549
50+ properties :: Properties '[ 'PropertyKey " path" 'TString]
51+ properties =
52+ emptyProperties
53+ & defineStringProperty
54+ # path
55+ " Set path to 'cabal-gild' executable"
56+ " cabal-gild"
57+
4658-- | Formatter provider of cabal gild.
4759-- Formats the given source in either a given Range or the whole Document.
4860-- If the provider fails an error is returned that can be displayed to the user.
49- provider :: Recorder (WithPriority Log ) -> FormattingHandler IdeState
50- provider recorder _ _ (FormatRange _) _ _ _ = do
61+ provider :: Recorder (WithPriority Log ) -> PluginId -> FormattingHandler IdeState
62+ provider recorder _ _ _ (FormatRange _) _ _ _ = do
5163 logWith recorder Info LogInvalidInvocationInfo
5264 throwError $ PluginInvalidParams " You cannot format a text-range using cabal-gild."
53- provider recorder _ide _ FormatText contents nfp _ = do
65+ provider recorder plId ideState _ FormatText contents nfp _ = do
5466 let cabalGildArgs = [" --stdin=" <> fp, " --input=-" ] -- < Read from stdin
55- x <- liftIO $ findExecutable " cabal-gild"
67+
68+ cabalGildExePath <- fmap T. unpack $ liftIO $ runAction " cabal-gild" ideState $ usePropertyAction # path plId properties
69+ x <- liftIO $ findExecutable cabalGildExePath
5670 case x of
5771 Just _ -> do
5872 log Debug $ LogReadCreateProcessInfo cabalGildArgs
5973 (exitCode, out, err) <-
6074 liftIO $ Process. readCreateProcessWithExitCode
61- ( proc " cabal-gild " cabalGildArgs
75+ ( proc cabalGildExePath cabalGildArgs
6276 )
6377 { cwd = Just $ takeDirectory fp
6478 }
@@ -71,8 +85,8 @@ provider recorder _ide _ FormatText contents nfp _ = do
7185 let fmtDiff = makeDiffTextEdit contents out
7286 pure $ InL fmtDiff
7387 Nothing -> do
74- log Error LogFormatterBinNotFound
75- throwError (PluginInternalError " No installation of cabal-gild could be found. Please install it into your global environment ." )
88+ log Error $ LogFormatterBinNotFound cabalGildExePath
89+ throwError (PluginInternalError " No installation of cabal-gild could be found. Please install it globally, or provide the full path to the executable ." )
7690 where
7791 fp = fromNormalizedFilePath nfp
7892 log = logWith recorder
0 commit comments