1
1
{-# LANGUAGE PolyKinds #-}
2
2
{-# LANGUAGE TypeFamilies #-}
3
+ {-# LANGUAGE MultiWayIf #-}
4
+ {-# LANGUAGE LambdaCase #-}
3
5
module Ide.Plugin.Brittany where
4
6
5
7
import Control.Exception (bracket_ )
6
8
import Control.Lens
7
9
import Control.Monad.IO.Class
8
10
import Control.Monad.Trans.Maybe (MaybeT , runMaybeT )
9
- import Data.Maybe (mapMaybe , maybeToList )
11
+ import Data.Maybe (mapMaybe , maybeToList , fromMaybe )
10
12
import Data.Semigroup
11
13
import Data.Text (Text )
12
14
import qualified Data.Text as T
@@ -23,6 +25,27 @@ import qualified Language.LSP.Types.Lens as J
23
25
import System.Environment (setEnv , unsetEnv )
24
26
import System.FilePath
25
27
28
+ -- These imports are for the temporary pPrintText & can be removed when
29
+ -- issue #2005 is resolved
30
+ import Language.Haskell.Brittany.Internal.Config.Types
31
+ import Language.Haskell.Brittany.Internal
32
+ import Language.Haskell.Brittany.Internal.Types
33
+ import Language.Haskell.Brittany.Internal.Utils
34
+ import Language.Haskell.Brittany.Internal.Obfuscation
35
+ import Language.Haskell.Brittany.Internal.Config
36
+ import Data.CZipWith
37
+ import Control.Monad.Trans.Class (lift )
38
+ import qualified Control.Monad.Trans.Except as ExceptT
39
+ import qualified Data.List as List
40
+ import qualified Data.Text as Text
41
+ import qualified Language.Haskell.GHC.ExactPrint as ExactPrint
42
+ import qualified Language.Haskell.GHC.ExactPrint.Types as ExactPrint
43
+ import qualified Data.Text.Lazy as TextL
44
+ import qualified DynFlags as GHC
45
+ import qualified GHC
46
+ import qualified GHC.LanguageExtensions.Type as GHC
47
+
48
+
26
49
descriptor :: PluginId -> PluginDescriptor IdeState
27
50
descriptor plId = (defaultPluginDescriptor plId)
28
51
{ pluginHandlers = mkFormattingHandlers provider
@@ -89,7 +112,11 @@ runBrittany tabSize df confPath text = do
89
112
}
90
113
91
114
config <- fromMaybeT (pure staticDefaultConfig) (readConfigsWithUserConfig cfg (maybeToList confPath))
92
- parsePrintModule config text
115
+ (errsAndWarnings, resultText) <- pPrintText config text
116
+ if any isError errsAndWarnings then
117
+ return $ Left errsAndWarnings
118
+ else
119
+ return $ Right resultText
93
120
94
121
fromMaybeT :: Monad m => m a -> MaybeT m a -> m a
95
122
fromMaybeT def act = runMaybeT act >>= maybe def return
@@ -115,3 +142,126 @@ showExtension other = Just $ "-X" ++ show other
115
142
116
143
getExtensions :: D. DynFlags -> [String ]
117
144
getExtensions = mapMaybe showExtension . S. toList . D. extensionFlags
145
+
146
+
147
+ -- | This is a temporary fix that allows us to format the text if brittany
148
+ -- throws warnings during pretty printing.
149
+ --
150
+ -- It should be removed when our PR to brittany is merged + released.
151
+ -- See:
152
+ -- - https://github.com/haskell/haskell-language-server/issues/2005
153
+ -- - https://github.com/lspitzner/brittany/pull/351
154
+ pPrintText
155
+ :: Config -- ^ global program config
156
+ -> Text -- ^ input text
157
+ -> IO ([BrittanyError ], Text ) -- ^ list of errors/warnings & result text
158
+ pPrintText config text =
159
+ fmap (either id id ) . ExceptT. runExceptT $ do
160
+ let ghcOptions = config & _conf_forward & _options_ghc & runIdentity
161
+ -- there is a good of code duplication between the following code and the
162
+ -- `pureModuleTransform` function. Unfortunately, there are also a good
163
+ -- amount of slight differences: This module is a bit more verbose, and
164
+ -- it tries to use the full-blown `parseModule` function which supports
165
+ -- CPP (but requires the input to be a file..).
166
+ let cppMode = config & _conf_preprocessor & _ppconf_CPPMode & confUnpack
167
+ -- the flag will do the following: insert a marker string
168
+ -- ("-- BRITANY_INCLUDE_HACK ") right before any lines starting with
169
+ -- "#include" before processing (parsing) input; and remove that marker
170
+ -- string from the transformation output.
171
+ -- The flag is intentionally misspelled to prevent clashing with
172
+ -- inline-config stuff.
173
+ let hackAroundIncludes =
174
+ config & _conf_preprocessor & _ppconf_hackAroundIncludes & confUnpack
175
+ let exactprintOnly = viaGlobal || viaDebug
176
+ where
177
+ viaGlobal = config & _conf_roundtrip_exactprint_only & confUnpack
178
+ viaDebug =
179
+ config & _conf_debug & _dconf_roundtrip_exactprint_only & confUnpack
180
+
181
+ let cppCheckFunc dynFlags = if GHC. xopt GHC. Cpp dynFlags
182
+ then case cppMode of
183
+ CPPModeAbort ->
184
+ return $ Left " Encountered -XCPP. Aborting."
185
+ CPPModeWarn ->
186
+ return $ Right True
187
+ CPPModeNowarn ->
188
+ return $ Right True
189
+ else return $ Right False
190
+ parseResult <- do
191
+ -- TODO: refactor this hack to not be mixed into parsing logic
192
+ let hackF s = if " #include" `List.isPrefixOf` s
193
+ then " -- BRITANY_INCLUDE_HACK " ++ s
194
+ else s
195
+ let hackTransform = if hackAroundIncludes && not exactprintOnly
196
+ then List. intercalate " \n " . fmap hackF . lines'
197
+ else id
198
+ liftIO $ parseModuleFromString ghcOptions
199
+ " stdin"
200
+ cppCheckFunc
201
+ (hackTransform $ Text. unpack text)
202
+ case parseResult of
203
+ Left left -> do
204
+ ExceptT. throwE ([ErrorInput left], text)
205
+ Right (anns, parsedSource, hasCPP) -> do
206
+ (inlineConf, perItemConf) <-
207
+ case
208
+ extractCommentConfigs anns (getTopLevelDeclNameMap parsedSource)
209
+ of
210
+ Left (err, input) -> do
211
+ let errMsg =
212
+ " Error: parse error in inline configuration: "
213
+ <> err
214
+ <> " in the string \" "
215
+ <> input
216
+ <> " \" ."
217
+ ExceptT. throwE ([ErrorInput errMsg], text)
218
+ Right c ->
219
+ pure c
220
+ let moduleConf = cZipWith fromOptionIdentity config inlineConf
221
+ let disableFormatting =
222
+ moduleConf & _conf_disable_formatting & confUnpack
223
+ (errsWarns, outSText, _) <- do
224
+ if
225
+ | disableFormatting -> do
226
+ pure ([] , text, False )
227
+ | exactprintOnly -> do
228
+ let r = Text. pack $ ExactPrint. exactPrint parsedSource anns
229
+ pure ([] , r, r /= text)
230
+ | otherwise -> do
231
+ (ews, outRaw) <- if hasCPP
232
+ then return
233
+ $ pPrintModule moduleConf perItemConf anns parsedSource
234
+ else liftIO $ pPrintModuleAndCheck moduleConf
235
+ perItemConf
236
+ anns
237
+ parsedSource
238
+ let hackF s = fromMaybe s $ TextL. stripPrefix
239
+ (TextL. pack " -- BRITANY_INCLUDE_HACK " )
240
+ s
241
+ let out = TextL. toStrict $ if hackAroundIncludes
242
+ then
243
+ TextL. intercalate (TextL. pack " \n " )
244
+ $ hackF
245
+ <$> TextL. splitOn (TextL. pack " \n " ) outRaw
246
+ else outRaw
247
+ out' <- if moduleConf & _conf_obfuscate & confUnpack
248
+ then lift $ obfuscate out
249
+ else pure out
250
+ pure (ews, out', out' /= text)
251
+ let customErrOrder ErrorInput {} = 4
252
+ customErrOrder LayoutWarning {} = - 1 :: Int
253
+ customErrOrder ErrorOutputCheck {} = 1
254
+ customErrOrder ErrorUnusedComment {} = 2
255
+ customErrOrder ErrorUnknownNode {} = - 2 :: Int
256
+ customErrOrder ErrorMacroConfig {} = 5
257
+ hasErrors =
258
+ if config & _conf_errorHandling & _econf_Werror & confUnpack
259
+ then not $ null errsWarns
260
+ else 0 < maximum (- 1 : fmap customErrOrder errsWarns)
261
+ return (errsWarns, if hasErrors then text else outSText)
262
+
263
+ isError :: BrittanyError -> Bool
264
+ isError = \ case
265
+ LayoutWarning {} -> False
266
+ ErrorUnknownNode {} -> False
267
+ _ -> True
0 commit comments