@@ -18,31 +18,31 @@ import Control.Monad
18
18
import Control.Monad.IO.Class
19
19
import Data.Bifunctor (first )
20
20
import Data.Maybe
21
+ import Data.Text (Text )
21
22
import qualified Data.Text as T
22
- import qualified Data.Text.IO as T
23
23
import Development.IDE hiding (pluginHandlers )
24
- import Development.IDE.GHC.Compat as Compat hiding (Cpp )
24
+ import Development.IDE.GHC.Compat as Compat hiding (Cpp , Warning ,
25
+ hang , vcat )
25
26
import qualified Development.IDE.GHC.Compat.Util as S
26
27
import GHC.LanguageExtensions.Type (Extension (Cpp ))
27
28
import Ide.Plugin.Properties
28
29
import Ide.PluginUtils (makeDiffTextEdit ,
29
30
usePropertyLsp )
30
31
import Ide.Types
31
32
import Language.LSP.Server hiding (defaultConfig )
32
- import Language.LSP.Types
33
+ import Language.LSP.Types hiding ( line )
33
34
import Language.LSP.Types.Lens (HasTabSize (tabSize ))
34
35
import Ormolu
35
36
import Ormolu.Config
36
37
import System.Exit
37
38
import System.FilePath
38
- import System.IO (stderr )
39
39
import System.Process.Run (cwd , proc )
40
40
import System.Process.Text (readCreateProcessWithExitCode )
41
41
42
- descriptor :: PluginId -> PluginDescriptor IdeState
43
- descriptor plId =
42
+ descriptor :: Recorder ( WithPriority LogEvent ) -> PluginId -> PluginDescriptor IdeState
43
+ descriptor recorder plId =
44
44
(defaultPluginDescriptor plId)
45
- { pluginHandlers = mkFormattingHandlers $ provider plId
45
+ { pluginHandlers = mkFormattingHandlers $ provider recorder plId
46
46
}
47
47
48
48
properties :: Properties '[ 'PropertyKey " external" 'TBoolean]
@@ -53,8 +53,8 @@ properties =
53
53
" Call out to an external \" fourmolu\" executable, rather than using the bundled library"
54
54
False
55
55
56
- provider :: PluginId -> FormattingHandler IdeState
57
- provider plId ideState typ contents fp fo = withIndefiniteProgress title Cancellable $ do
56
+ provider :: Recorder ( WithPriority LogEvent ) -> PluginId -> FormattingHandler IdeState
57
+ provider recorder plId ideState typ contents fp fo = withIndefiniteProgress title Cancellable $ do
58
58
fileOpts <-
59
59
maybe [] (convertDynFlags . hsc_dflags . hscEnv)
60
60
<$> liftIO (runAction " Fourmolu" ideState $ use GhcSession fp)
@@ -75,7 +75,7 @@ provider plId ideState typ contents fp fo = withIndefiniteProgress title Cancell
75
75
{ noCabal = v >= [" 0" , " 7" ]
76
76
}
77
77
Nothing -> do
78
- T. hPutStrLn stderr " couldn't get Fourmolu version "
78
+ logWith recorder Warning $ NoVersion out
79
79
pure CLIVersionInfo
80
80
{ noCabal = True
81
81
}
@@ -91,11 +91,12 @@ provider plId ideState typ contents fp fo = withIndefiniteProgress title Cancell
91
91
<> map (" -o" <> ) fileOpts
92
92
){cwd = Just $ takeDirectory fp'}
93
93
contents
94
- T. hPutStrLn stderr err
95
94
case exitCode of
96
- ExitSuccess ->
95
+ ExitSuccess -> do
96
+ logWith recorder Debug $ StdErr err
97
97
pure . Right $ makeDiffTextEdit contents out
98
- ExitFailure n ->
98
+ ExitFailure n -> do
99
+ logWith recorder Info $ StdErr err
99
100
pure . Left . responseError $ " Fourmolu failed with exit code " <> T. pack (show n)
100
101
else do
101
102
let format fourmoluConfig =
@@ -125,13 +126,10 @@ provider plId ideState typ contents fp fo = withIndefiniteProgress title Cancell
125
126
}
126
127
in liftIO (loadConfigFile fp') >>= \ case
127
128
ConfigLoaded file opts -> liftIO $ do
128
- putStrLn $ " Loaded Fourmolu config from: " <> file
129
+ logWith recorder Info $ ConfigPath file
129
130
format opts
130
131
ConfigNotFound searchDirs -> liftIO $ do
131
- putStrLn
132
- . unlines
133
- $ (" No " ++ show configFileName ++ " found in any of:" ) :
134
- map (" " ++ ) searchDirs
132
+ logWith recorder Info $ NoConfigPath searchDirs
135
133
format emptyOptions
136
134
where
137
135
emptyOptions =
@@ -170,6 +168,21 @@ provider plId ideState typ contents fp fo = withIndefiniteProgress title Cancell
170
168
FormatRange (Range (Position sl _) (Position el _)) ->
171
169
RegionIndices (Just $ fromIntegral $ sl + 1 ) (Just $ fromIntegral $ el + 1 )
172
170
171
+ data LogEvent
172
+ = NoVersion Text
173
+ | ConfigPath FilePath
174
+ | NoConfigPath [FilePath ]
175
+ | StdErr Text
176
+ deriving (Show )
177
+
178
+ instance Pretty LogEvent where
179
+ pretty = \ case
180
+ NoVersion t -> " Couldn't get Fourmolu version:" <> line <> indent 2 (pretty t)
181
+ ConfigPath p -> " Loaded Fourmolu config from: " <> pretty (show p)
182
+ NoConfigPath ps -> " No " <> pretty configFileName <> " found in any of:"
183
+ <> line <> indent 2 (vsep (map (pretty . show ) ps))
184
+ StdErr t -> " Fourmolu stderr:" <> line <> indent 2 (pretty t)
185
+
173
186
convertDynFlags :: DynFlags -> [String ]
174
187
convertDynFlags df =
175
188
let pp = [" -pgmF=" <> p | not (null p)]
0 commit comments