Skip to content

Commit 1e743a0

Browse files
committed
Ormolu already handles file pragmas
ms_hspp_opts contains the LANGUAGE and OPTIONS pragmas what we want here is the cabal/stack options instead
1 parent 6680505 commit 1e743a0

File tree

1 file changed

+20
-17
lines changed

1 file changed

+20
-17
lines changed

Diff for: src/Ide/Plugin/Ormolu.hs

+20-17
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,7 @@
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

76
module Ide.Plugin.Ormolu
87
(
@@ -12,20 +11,24 @@ module Ide.Plugin.Ormolu
1211
where
1312

1413
import Control.Exception
15-
import qualified Data.Text as T
14+
import qualified Data.Text as T
1615
import 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)
1719
import Development.IDE.Types.Diagnostics as D
1820
import 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
2123
import GHC
2224
import GHC.LanguageExtensions.Type
23-
import Ide.Types
24-
import Ide.PluginUtils
25+
import GhcPlugins (HscEnv (hsc_dflags))
2526
import Ide.Plugin.Formatter
27+
import Ide.PluginUtils
28+
import Ide.Types
2629
import Language.Haskell.LSP.Types
2730
import Ormolu
28-
import Text.Regex.TDFA.Text()
31+
import Text.Regex.TDFA.Text ()
2932

3033
-- ---------------------------------------------------------------------
3134

@@ -39,10 +42,9 @@ descriptor plId = (defaultPluginDescriptor plId)
3942
provider :: FormattingProvider IO
4043
provider _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

8083
showExtension :: Extension -> String
81-
showExtension Cpp = "-XCPP"
84+
showExtension Cpp = "-XCPP"
8285
showExtension other = "-X" ++ show other

0 commit comments

Comments
 (0)