55{-# LANGUAGE NamedFieldPuns #-}
66{-# LANGUAGE OverloadedLabels #-}
77{-# LANGUAGE OverloadedStrings #-}
8+ {-# LANGUAGE RecordWildCards #-}
89{-# LANGUAGE TypeApplications #-}
910{-# LANGUAGE TypeOperators #-}
1011
@@ -71,39 +72,19 @@ provider recorder plId ideState typ contents fp fo = ExceptT $ withIndefinitePro
7172 <$> liftIO (runAction " Fourmolu" ideState $ use GhcSession fp)
7273 useCLI <- liftIO $ runAction " Fourmolu" ideState $ usePropertyAction # external plId properties
7374 if useCLI
74- then mapExceptT liftIO $ ExceptT
75- $ handle @ IOException
76- (pure . Left . PluginInternalError . T. pack . show )
77- $ runExceptT $ cliHandler fileOpts
75+ then ExceptT . liftIO $
76+ handle @ IOException (pure . Left . PluginInternalError . T. pack . show ) $
77+ runExceptT (cliHandler fileOpts)
7878 else do
7979 logWith recorder Debug $ LogCompiledInVersion VERSION_fourmolu
80- let format fourmoluConfig = ExceptT $
81- bimap (PluginInternalError . T. pack . show ) (InL . makeDiffTextEdit contents)
82- #if MIN_VERSION_fourmolu(0,11,0)
83- <$> try @ OrmoluException (ormolu config fp' contents)
84- #else
85- <$> try @ OrmoluException (ormolu config fp' (T. unpack contents))
86- #endif
87- where
88- printerOpts = cfgFilePrinterOpts fourmoluConfig
89- config =
90- defaultConfig
91- { cfgDynOptions = map DynOption fileOpts
92- , cfgFixityOverrides = cfgFileFixities fourmoluConfig
93- , cfgRegion = region
94- , cfgDebug = False
95- , cfgPrinterOpts =
96- fillMissingPrinterOpts
97- (printerOpts <> lspPrinterOpts)
98- defaultPrinterOpts
99- }
100- in liftIO (loadConfigFile fp') >>= \ case
80+ FourmoluConfig {.. } <-
81+ liftIO (loadConfigFile fp') >>= \ case
10182 ConfigLoaded file opts -> do
10283 logWith recorder Info $ ConfigPath file
103- mapExceptT liftIO $ format opts
84+ pure opts
10485 ConfigNotFound searchDirs -> do
10586 logWith recorder Info $ NoConfigPath searchDirs
106- mapExceptT liftIO $ format emptyConfig
87+ pure emptyConfig
10788 ConfigParseError f err -> do
10889 lift $ sendNotification SMethod_WindowShowMessage $
10990 ShowMessageParams
@@ -113,6 +94,18 @@ provider recorder plId ideState typ contents fp fo = ExceptT $ withIndefinitePro
11394 throwError $ PluginInternalError errorMessage
11495 where
11596 errorMessage = " Failed to load " <> T. pack f <> " : " <> T. pack (show err)
97+
98+ let config =
99+ defaultConfig
100+ { cfgDynOptions = map DynOption fileOpts
101+ , cfgFixityOverrides = cfgFileFixities
102+ , cfgRegion = region
103+ , cfgDebug = False
104+ , cfgPrinterOpts = resolvePrinterOpts [lspPrinterOpts, cfgFilePrinterOpts]
105+ }
106+ ExceptT . liftIO $
107+ bimap (PluginInternalError . T. pack . show ) (InL . makeDiffTextEdit contents)
108+ <$> try @ OrmoluException (ormolu config fp' contents)
116109 where
117110 fp' = fromNormalizedFilePath fp
118111 title = " Formatting " <> T. pack (takeFileName fp')
@@ -200,3 +193,8 @@ newtype CLIVersionInfo = CLIVersionInfo
200193
201194mwhen :: Monoid a => Bool -> a -> a
202195mwhen b x = if b then x else mempty
196+
197+ #if !MIN_VERSION_fourmolu(0,14,0)
198+ resolvePrinterOpts :: [PrinterOptsPartial ] -> PrinterOptsTotal
199+ resolvePrinterOpts = foldr fillMissingPrinterOpts defaultPrinterOpts
200+ #endif
0 commit comments