1- {-# LANGUAGE RecordWildCards #-}
2- {-# LANGUAGE OverloadedStrings #-}
1+ {-# LANGUAGE OverloadedStrings #-}
2+ {-# LANGUAGE RecordWildCards #-}
33{-# LANGUAGE ScopedTypeVariables #-}
4- {-# LANGUAGE TypeApplications #-}
5- {-# LANGUAGE ViewPatterns #-}
4+ {-# LANGUAGE TypeApplications #-}
65
76module Ide.Plugin.Ormolu
87 (
@@ -12,20 +11,24 @@ module Ide.Plugin.Ormolu
1211where
1312
1413import Control.Exception
15- import qualified Data.Text as T
14+ import qualified Data.Text as T
1615import Development.IDE.Core.Rules
16+ import Development.IDE.Core.RuleTypes (GhcSession (GhcSession ))
17+ import Development.IDE.Core.Shake (use )
18+ import Development.IDE.GHC.Util (hscEnv )
1719import Development.IDE.Types.Diagnostics as D
1820import Development.IDE.Types.Location
19- import qualified DynFlags as D
20- import qualified EnumSet as S
21+ import qualified DynFlags as D
22+ import qualified EnumSet as S
2123import GHC
2224import GHC.LanguageExtensions.Type
23- import Ide.Types
24- import Ide.PluginUtils
25+ import GhcPlugins (HscEnv (hsc_dflags ))
2526import Ide.Plugin.Formatter
27+ import Ide.PluginUtils
28+ import Ide.Types
2629import Language.Haskell.LSP.Types
2730import Ormolu
28- import Text.Regex.TDFA.Text ()
31+ import Text.Regex.TDFA.Text ()
2932
3033-- ---------------------------------------------------------------------
3134
@@ -39,10 +42,9 @@ descriptor plId = (defaultPluginDescriptor plId)
3942provider :: FormattingProvider IO
4043provider _lf ideState typ contents fp _ = do
4144 let
42- fromDyn :: ParsedModule -> IO [DynOption ]
43- fromDyn pmod =
45+ fromDyn :: DynFlags -> IO [DynOption ]
46+ fromDyn df =
4447 let
45- df = ms_hspp_opts $ pm_mod_summary pmod
4648 pp =
4749 let p = D. sPgm_F $ D. settings df
4850 in if null p then [] else [" -pgmF=" <> p]
@@ -51,10 +53,11 @@ provider _lf ideState typ contents fp _ = do
5153 in
5254 return $ map DynOption $ pp <> pm <> ex
5355
54- m_parsed <- runAction " Ormolu" ideState $ getParsedModule fp
55- fileOpts <- case m_parsed of
56+ ghc <- runAction " Ormolu" ideState $ use GhcSession fp
57+ let df = hsc_dflags . hscEnv <$> ghc
58+ fileOpts <- case df of
5659 Nothing -> return []
57- Just pm -> fromDyn pm
60+ Just df -> fromDyn df
5861
5962 let
6063 fullRegion = RegionIndices Nothing Nothing
@@ -78,5 +81,5 @@ provider _lf ideState typ contents fp _ = do
7881 ret (Right new) = Right (makeDiffTextEdit contents new)
7982
8083showExtension :: Extension -> String
81- showExtension Cpp = " -XCPP"
84+ showExtension Cpp = " -XCPP"
8285showExtension other = " -X" ++ show other
0 commit comments