Skip to content

Commit

Permalink
Use the runtime ghc libdir for ghc-exactprint (#1225)
Browse files Browse the repository at this point in the history
* Use runtime libdir for ghc-exactprint

* Use released apply-refact and master ghc-exactprint

* Rephrase warning

* Add required uniplate-1.6.13

* Use bracket_ to simplify code

* Use runtime ghc libdir for brittany

Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
  • Loading branch information
jneira and mergify[bot] authored Jan 19, 2021
1 parent 18227b3 commit 4ecf9d3
Show file tree
Hide file tree
Showing 12 changed files with 78 additions and 62 deletions.
6 changes: 3 additions & 3 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -15,8 +15,8 @@ packages:

source-repository-package
type: git
location: https://github.com/mpickering/apply-refact.git
tag: 4fbd3a3a9b408bd31080848feb6b78e13c3eeb6d
location: https://github.com/alanz/ghc-exactprint.git
tag: 6748e24da18a6cea985d20cc3e1e7920cb743795

tests: true

Expand All @@ -30,7 +30,7 @@ package ghcide

write-ghc-environment-files: never

index-state: 2021-01-14T12:49:26Z
index-state: 2021-01-17T17:47:48Z

allow-newer:
active:base,
Expand Down
17 changes: 11 additions & 6 deletions plugins/default/src/Ide/Plugin/Brittany.hs
Original file line number Diff line number Diff line change
@@ -1,22 +1,24 @@
module Ide.Plugin.Brittany where

import Control.Exception (bracket_)
import Control.Lens
import Control.Monad.IO.Class
import Control.Monad.Trans.Maybe (MaybeT, runMaybeT)
import Data.Coerce
import Data.Maybe (maybeToList)
import Data.Semigroup
import Data.Text (Text)
import qualified Data.Text as T
import Development.IDE
-- import Development.IDE.Plugin.Formatter
import Development.IDE.GHC.Compat (topDir, ModSummary(ms_hspp_opts))
import Language.Haskell.Brittany
import Language.Haskell.LSP.Types as J
import qualified Language.Haskell.LSP.Types.Lens as J
import Ide.PluginUtils
import Ide.Types

import System.FilePath
import Data.Maybe (maybeToList)
import System.Environment (setEnv, unsetEnv)

descriptor :: PluginId -> PluginDescriptor IdeState
descriptor plId = (defaultPluginDescriptor plId)
Expand All @@ -28,14 +30,17 @@ descriptor plId = (defaultPluginDescriptor plId)
-- If the provider fails an error is returned that can be displayed to the user.
provider
:: FormattingProvider IdeState IO
provider _lf _ideState typ contents fp opts = do
provider _lf ide typ contents nfp opts = do
-- text uri formatType opts = pluginGetFile "brittanyCmd: " uri $ \fp -> do
confFile <- liftIO $ getConfFile fp
confFile <- liftIO $ getConfFile nfp
let (range, selectedContents) = case typ of
FormatText -> (fullRange contents, contents)
FormatRange r -> (normalize r, extractRange r contents)

res <- formatText confFile opts selectedContents
(modsum, _) <- runAction "brittany" ide $ use_ GetModSummary nfp
let dflags = ms_hspp_opts modsum
let withRuntimeLibdir = bracket_ (setEnv key $ topDir dflags) (unsetEnv key)
where key = "GHC_EXACTPRINT_GHC_LIBDIR"
res <- withRuntimeLibdir $ formatText confFile opts selectedContents
case res of
Left err -> return $ Left $ responseError (T.pack $ "brittanyCmd: " ++ unlines (map showErr err))
Right newText -> return $ Right $ J.List [TextEdit range newText]
Expand Down
17 changes: 14 additions & 3 deletions plugins/hls-hlint-plugin/src/Ide/Plugin/Hlint.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,10 +38,12 @@ import Development.IDE.Core.Shake (getDiagnostics)
import Data.List (nub)
import "ghc-lib" GHC hiding (DynFlags(..), ms_hspp_opts)
import "ghc-lib-parser" GHC.LanguageExtensions (Extension)
import "ghc" DynFlags as RealGHC.DynFlags (topDir)
import "ghc" GHC as RealGHC (DynFlags(..))
import "ghc" HscTypes as RealGHC.HscTypes (hsc_dflags, ms_hspp_opts)
import qualified "ghc" EnumSet as EnumSet
import Language.Haskell.GhclibParserEx.GHC.Driver.Session as GhclibParserEx (readExtension)
import System.Environment(setEnv, unsetEnv)
import System.FilePath (takeFileName)
import System.IO (hPutStr, noNewlineTranslation, hSetNewlineMode, utf8, hSetEncoding, IOMode(WriteMode), withFile, hClose)
import System.IO.Temp
Expand Down Expand Up @@ -359,6 +361,8 @@ applyHint ide nfp mhint =
let fp = fromNormalizedFilePath nfp
(_, mbOldContent) <- liftIO $ runAction' $ getFileContents nfp
oldContent <- maybe (liftIO $ T.readFile fp) return mbOldContent
(modsum, _) <- liftIO $ runAction' $ use_ GetModSummary nfp
let dflags = ms_hspp_opts modsum
-- set Nothing as "position" for "applyRefactorings" because
-- applyRefactorings expects the provided position to be _within_ the scope
-- of each refactoring it will apply.
Expand All @@ -380,6 +384,15 @@ applyHint ide nfp mhint =
hSetEncoding h utf8
hSetNewlineMode h noNewlineTranslation
hPutStr h (T.unpack txt)
-- Setting a environment variable with the libdir used by ghc-exactprint.
-- It is a workaround for an error caused by the use of a hadcoded at compile time libdir
-- in ghc-exactprint that makes dependent executables non portables.
-- See https://github.com/alanz/ghc-exactprint/issues/96.
-- WARNING: this code is not thread safe, so if you try to apply several async refactorings
-- it could fail. That case is not very likely so we assume the risk.
let withRuntimeLibdir :: IO a -> IO a
withRuntimeLibdir = bracket_ (setEnv key $ topDir dflags) (unsetEnv key)
where key = "GHC_EXACTPRINT_GHC_LIBDIR"
res <-
liftIO $ withSystemTempFile (takeFileName fp) $ \temp h -> do
hClose h
Expand All @@ -389,7 +402,7 @@ applyHint ide nfp mhint =
-- We have to reparse extensions to remove the invalid ones
let (enabled, disabled, _invalid) = parseExtensions $ map show exts
let refactExts = map show $ enabled ++ disabled
(Right <$> applyRefactorings Nothing commands temp refactExts)
(Right <$> withRuntimeLibdir (applyRefactorings Nothing commands temp refactExts))
`catches` errorHandlers
#else
mbParsedModule <- liftIO $ runAction' $ getParsedModuleWithComments nfp
Expand All @@ -399,8 +412,6 @@ applyHint ide nfp mhint =
Just pm -> do
let anns = pm_annotations pm
let modu = pm_parsed_source pm
(modsum, _) <- liftIO $ runAction' $ use_ GetModSummary nfp
let dflags = ms_hspp_opts modsum
-- apply-refact uses RigidLayout
let rigidLayout = deltaOptions RigidLayout
(anns', modu') <-
Expand Down
12 changes: 7 additions & 5 deletions stack-8.10.1.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -19,17 +19,20 @@ ghc-options:
"$everything": -haddock

extra-deps:
- git: https://github.com/mpickering/apply-refact.git
commit: 4fbd3a3a9b408bd31080848feb6b78e13c3eeb6d
- apply-refact-0.9.0.0
- brittany-0.13.1.0
- Cabal-3.0.2.0
- clock-0.7.2
- data-tree-print-0.1.0.2@rev:2
- floskell-0.10.4
- fourmolu-0.3.0.0
- ghc-exactprint-0.6.3.3
# - ghc-exactprint-0.6.3.3
- git: https://github.com/alanz/ghc-exactprint.git
commit: 6748e24da18a6cea985d20cc3e1e7920cb743795
- ghc-lib-8.10.3.20201220
- ghc-lib-parser-8.10.3.20201220
- haskell-lsp-0.23.0.0
- haskell-lsp-types-0.23.0.0
- heapsize-0.3.0
- hie-bios-0.7.1
- hlint-3.2.3
Expand All @@ -46,8 +49,7 @@ extra-deps:
- stylish-haskell-0.12.2.0
- semigroups-0.18.5
- temporary-1.2.1.1
- haskell-lsp-0.23.0.0
- haskell-lsp-types-0.23.0.0
- uniplate-1.6.13

configure-options:
ghcide:
Expand Down
9 changes: 5 additions & 4 deletions stack-8.10.2.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -19,16 +19,19 @@ ghc-options:
"$everything": -haddock

extra-deps:
- git: https://github.com/mpickering/apply-refact.git
commit: 4fbd3a3a9b408bd31080848feb6b78e13c3eeb6d
- apply-refact-0.9.0.0
- brittany-0.13.1.0
- Cabal-3.0.2.0
- clock-0.7.2
- data-tree-print-0.1.0.2@rev:2
- floskell-0.10.4
- fourmolu-0.3.0.0
- git: https://github.com/alanz/ghc-exactprint.git
commit: 6748e24da18a6cea985d20cc3e1e7920cb743795
- ghc-lib-8.10.3.20201220
- ghc-lib-parser-8.10.3.20201220
- haskell-lsp-0.23.0.0
- haskell-lsp-types-0.23.0.0
- heapsize-0.3.0
- implicit-hie-cradle-0.3.0.2
- implicit-hie-0.1.2.5
Expand All @@ -39,8 +42,6 @@ extra-deps:
- stylish-haskell-0.12.2.0
- semigroups-0.18.5
- temporary-1.2.1.1
- haskell-lsp-0.23.0.0
- haskell-lsp-types-0.23.0.0

configure-options:
ghcide:
Expand Down
7 changes: 4 additions & 3 deletions stack-8.10.3.yaml
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
resolver: nightly-2021-01-01 # first ghc-8.10.3 nightly
resolver: nightly-2021-01-17

packages:
- .
Expand All @@ -19,14 +19,15 @@ ghc-options:
"$everything": -haddock

extra-deps:
- git: https://github.com/mpickering/apply-refact.git
commit: 4fbd3a3a9b408bd31080848feb6b78e13c3eeb6d
- apply-refact-0.9.0.0
- brittany-0.13.1.0
- Cabal-3.0.2.0
- clock-0.7.2
- data-tree-print-0.1.0.2@rev:2
- floskell-0.10.4
- fourmolu-0.3.0.0
- git: https://github.com/alanz/ghc-exactprint.git
commit: 6748e24da18a6cea985d20cc3e1e7920cb743795
- heapsize-0.3.0
- implicit-hie-cradle-0.3.0.2
- implicit-hie-0.1.2.5
Expand Down
10 changes: 5 additions & 5 deletions stack-8.6.4.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -21,9 +21,7 @@ ghc-options:

extra-deps:
- aeson-1.5.2.0
# - apply-refact-0.8.2.1
- git: https://github.com/mpickering/apply-refact.git
commit: 4fbd3a3a9b408bd31080848feb6b78e13c3eeb6d
- apply-refact-0.9.0.0
- ansi-terminal-0.10.3
- base-compat-0.10.5
- brittany-0.13.1.0
Expand All @@ -36,10 +34,11 @@ extra-deps:
- floskell-0.10.4
- fourmolu-0.3.0.0
- fuzzy-0.1.0.0
# - ghcide-0.1.0
- ghc-check-0.5.0.1
- ghc-events-0.13.0
- ghc-exactprint-0.6.3.3
# - ghc-exactprint-0.6.3.3
- git: https://github.com/alanz/ghc-exactprint.git
commit: 6748e24da18a6cea985d20cc3e1e7920cb743795
- ghc-lib-8.10.3.20201220
- ghc-lib-parser-8.10.3.20201220
- ghc-lib-parser-ex-8.10.0.17
Expand Down Expand Up @@ -80,6 +79,7 @@ extra-deps:
- these-1.1.1.1
- type-equality-1
- topograph-1
- uniplate-1.6.13
- with-utf8-1.0.2.1@sha256:95c02fffa643ddbeb092359802a512007c3e644cd509809f4716ad54592c437b,3057
- th-env-0.1.0.2@sha256:d8f1f37f42a8f1a22404d7d0579528af18f5dac7232cca6bdbd5117c115a0ad5,1370

Expand Down
10 changes: 5 additions & 5 deletions stack-8.6.5.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -20,9 +20,7 @@ ghc-options:

extra-deps:
- aeson-1.5.2.0
# - apply-refact-0.8.2.1
- git: https://github.com/mpickering/apply-refact.git
commit: 4fbd3a3a9b408bd31080848feb6b78e13c3eeb6d
- apply-refact-0.9.0.0
- ansi-terminal-0.10.3
- base-compat-0.10.5
- brittany-0.13.1.0
Expand All @@ -35,10 +33,11 @@ extra-deps:
- floskell-0.10.4
- fourmolu-0.3.0.0
- fuzzy-0.1.0.0
# - ghcide-0.1.0
- ghc-check-0.5.0.1
- ghc-events-0.13.0
- ghc-exactprint-0.6.3.3
# - ghc-exactprint-0.6.3.3
- git: https://github.com/alanz/ghc-exactprint.git
commit: 6748e24da18a6cea985d20cc3e1e7920cb743795
- ghc-lib-8.10.3.20201220
- ghc-lib-parser-8.10.3.20201220
- ghc-lib-parser-ex-8.10.0.17
Expand Down Expand Up @@ -79,6 +78,7 @@ extra-deps:
- these-1.1.1.1
- type-equality-1
- topograph-1
- uniplate-1.6.13
- with-utf8-1.0.2.1@sha256:95c02fffa643ddbeb092359802a512007c3e644cd509809f4716ad54592c437b,3057
- th-env-0.1.0.2@sha256:d8f1f37f42a8f1a22404d7d0579528af18f5dac7232cca6bdbd5117c115a0ad5,1370

Expand Down
10 changes: 5 additions & 5 deletions stack-8.8.2.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -20,9 +20,7 @@ ghc-options:

extra-deps:
- aeson-1.5.2.0
# - apply-refact-0.8.2.1
- git: https://github.com/mpickering/apply-refact.git
commit: 4fbd3a3a9b408bd31080848feb6b78e13c3eeb6d
- apply-refact-0.9.0.0
- brittany-0.13.1.0
- butcher-1.3.3.2
- bytestring-trie-0.2.5.0
Expand All @@ -31,10 +29,11 @@ extra-deps:
- extra-1.7.3
- floskell-0.10.4
- fourmolu-0.3.0.0
# - ghcide-0.6.0
- ghc-check-0.5.0.1
- ghc-events-0.13.0
- ghc-exactprint-0.6.3.3
# - ghc-exactprint-0.6.3.3
- git: https://github.com/alanz/ghc-exactprint.git
commit: 6748e24da18a6cea985d20cc3e1e7920cb743795
- ghc-lib-8.10.3.20201220
- ghc-lib-parser-8.10.3.20201220
- ghc-lib-parser-ex-8.10.0.17
Expand Down Expand Up @@ -64,6 +63,7 @@ extra-deps:
- stylish-haskell-0.12.2.0
- temporary-1.2.1.1
- these-1.1.1.1
- uniplate-1.6.13
- with-utf8-1.0.2.1@sha256:95c02fffa643ddbeb092359802a512007c3e644cd509809f4716ad54592c437b,3057
- th-env-0.1.0.2@sha256:d8f1f37f42a8f1a22404d7d0579528af18f5dac7232cca6bdbd5117c115a0ad5,1370

Expand Down
16 changes: 7 additions & 9 deletions stack-8.8.3.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -20,9 +20,7 @@ ghc-options:

extra-deps:
- aeson-1.5.2.0
# - apply-refact-0.8.2.1
- git: https://github.com/mpickering/apply-refact.git
commit: 4fbd3a3a9b408bd31080848feb6b78e13c3eeb6d
- apply-refact-0.9.0.0
- brittany-0.13.1.0
- bytestring-trie-0.2.5.0
- cabal-plan-0.6.2.0
Expand All @@ -31,11 +29,14 @@ extra-deps:
- extra-1.7.3
- floskell-0.10.4
- fourmolu-0.3.0.0
# - ghcide-0.6.0
- ghc-exactprint-0.6.3.3
# - ghc-exactprint-0.6.3.3
- git: https://github.com/alanz/ghc-exactprint.git
commit: 6748e24da18a6cea985d20cc3e1e7920cb743795
- ghc-lib-8.10.3.20201220
- ghc-lib-parser-8.10.3.20201220
- ghc-trace-events-0.1.2.1
- haskell-lsp-0.23.0.0
- haskell-lsp-types-0.23.0.0
- haskell-src-exts-1.21.1
- heapsize-0.3.0
- hie-bios-0.7.1
Expand All @@ -54,12 +55,9 @@ extra-deps:
- refinery-0.3.0.0
- retrie-0.1.1.1
- semigroups-0.18.5
# - github: wz1000/shake
# commit: fb3859dca2e54d1bbb2c873e68ed225fa179fbef
- stylish-haskell-0.12.2.0
- temporary-1.2.1.1
- haskell-lsp-0.23.0.0
- haskell-lsp-types-0.23.0.0
- uniplate-1.6.13

configure-options:
ghcide:
Expand Down
16 changes: 7 additions & 9 deletions stack-8.8.4.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -20,21 +20,22 @@ ghc-options:

extra-deps:
- aeson-1.5.2.0
# - apply-refact-0.8.2.1
- git: https://github.com/mpickering/apply-refact.git
commit: 4fbd3a3a9b408bd31080848feb6b78e13c3eeb6d
- apply-refact-0.9.0.0
- brittany-0.13.1.0
- bytestring-trie-0.2.5.0
- cabal-plan-0.6.2.0
- clock-0.7.2
- constrained-dynamic-0.1.0.0
- floskell-0.10.4
- fourmolu-0.3.0.0
# - ghcide-0.6.0
- ghc-exactprint-0.6.3.3
# - ghc-exactprint-0.6.3.3
- git: https://github.com/alanz/ghc-exactprint.git
commit: 6748e24da18a6cea985d20cc3e1e7920cb743795
- ghc-lib-8.10.3.20201220
- ghc-lib-parser-8.10.3.20201220
- ghc-trace-events-0.1.2.1
- haskell-lsp-0.23.0.0
- haskell-lsp-types-0.23.0.0
- haskell-src-exts-1.21.1
- heapsize-0.3.0
- hie-bios-0.7.1
Expand All @@ -52,12 +53,9 @@ extra-deps:
- refinery-0.3.0.0
- retrie-0.1.1.1
- semigroups-0.18.5
# - github: wz1000/shake
# commit: fb3859dca2e54d1bbb2c873e68ed225fa179fbef
- stylish-haskell-0.12.2.0
- temporary-1.2.1.1
- haskell-lsp-0.23.0.0
- haskell-lsp-types-0.23.0.0
- uniplate-1.6.13

configure-options:
ghcide:
Expand Down
Loading

0 comments on commit 4ecf9d3

Please sign in to comment.