1
+ {-# LANGUAGE CPP #-}
2
+ {-# LANGUAGE DataKinds #-}
1
3
{-# LANGUAGE DisambiguateRecordFields #-}
2
4
{-# LANGUAGE LambdaCase #-}
5
+ {-# LANGUAGE OverloadedLabels #-}
3
6
{-# LANGUAGE OverloadedStrings #-}
4
7
{-# LANGUAGE TypeApplications #-}
5
- {-# LANGUAGE DataKinds #-}
6
- {-# LANGUAGE OverloadedLabels #-}
7
8
8
9
module Ide.Plugin.Fourmolu (
9
10
descriptor ,
@@ -23,16 +24,18 @@ import Development.IDE.GHC.Compat as Compat hiding (Cpp)
23
24
import qualified Development.IDE.GHC.Compat.Util as S
24
25
import GHC.LanguageExtensions.Type (Extension (Cpp ))
25
26
import Ide.Plugin.Properties
26
- import Ide.PluginUtils (makeDiffTextEdit , usePropertyLsp )
27
+ import Ide.PluginUtils (makeDiffTextEdit ,
28
+ usePropertyLsp )
27
29
import Ide.Types
28
30
import Language.LSP.Server hiding (defaultConfig )
29
31
import Language.LSP.Types
30
32
import Language.LSP.Types.Lens (HasTabSize (tabSize ))
31
33
import Ormolu
34
+ import Ormolu.Config
32
35
import System.Exit
33
36
import System.FilePath
34
37
import System.IO (stderr )
35
- import System.Process.Run (proc , cwd )
38
+ import System.Process.Run (cwd , proc )
36
39
import System.Process.Text (readCreateProcessWithExitCode )
37
40
38
41
descriptor :: PluginId -> PluginDescriptor IdeState
@@ -78,10 +81,17 @@ provider plId ideState typ contents fp fo = withIndefiniteProgress title Cancell
78
81
ExitFailure n ->
79
82
pure . Left . responseError $ " Fourmolu failed with exit code " <> T. pack (show n)
80
83
else do
81
- let format printerOpts =
84
+ let format fourmoluConfig =
82
85
first (mkError . show )
83
86
<$> try @ OrmoluException (makeDiffTextEdit contents <$> ormolu config fp' (T. unpack contents))
84
87
where
88
+ printerOpts =
89
+ #if MIN_VERSION_fourmolu(0,7,0)
90
+ cfgFilePrinterOpts fourmoluConfig
91
+ #else
92
+ fourmoluConfig
93
+
94
+ #endif
85
95
config =
86
96
defaultConfig
87
97
{ cfgDynOptions = map DynOption fileOpts
@@ -91,6 +101,10 @@ provider plId ideState typ contents fp fo = withIndefiniteProgress title Cancell
91
101
fillMissingPrinterOpts
92
102
(printerOpts <> lspPrinterOpts)
93
103
defaultPrinterOpts
104
+ #if MIN_VERSION_fourmolu(0,7,0)
105
+ , cfgFixityOverrides =
106
+ cfgFileFixities fourmoluConfig
107
+ #endif
94
108
}
95
109
in liftIO (loadConfigFile fp') >>= \ case
96
110
ConfigLoaded file opts -> liftIO $ do
@@ -101,16 +115,33 @@ provider plId ideState typ contents fp fo = withIndefiniteProgress title Cancell
101
115
. unlines
102
116
$ (" No " ++ show configFileName ++ " found in any of:" ) :
103
117
map (" " ++ ) searchDirs
104
- format mempty
105
- ConfigParseError f (_, err) -> do
118
+ format emptyOptions
119
+ where
120
+ emptyOptions =
121
+ #if MIN_VERSION_fourmolu(0,7,0)
122
+ FourmoluConfig
123
+ { cfgFilePrinterOpts = mempty
124
+ , cfgFileFixities = mempty
125
+ }
126
+ #else
127
+ mempty
128
+ #endif
129
+
130
+ ConfigParseError f err -> do
106
131
sendNotification SWindowShowMessage $
107
132
ShowMessageParams
108
133
{ _xtype = MtError
109
134
, _message = errorMessage
110
135
}
111
136
return . Left $ responseError errorMessage
112
137
where
113
- errorMessage = " Failed to load " <> T. pack f <> " : " <> T. pack err
138
+ errorMessage = " Failed to load " <> T. pack f <> " : " <> T. pack (convertErr err)
139
+ convertErr =
140
+ #if MIN_VERSION_fourmolu(0,7,0)
141
+ show
142
+ #else
143
+ snd
144
+ #endif
114
145
where
115
146
fp' = fromNormalizedFilePath fp
116
147
title = " Formatting " <> T. pack (takeFileName fp')
0 commit comments