Skip to content

Commit 90d71ce

Browse files
joyfulmantismichaelpjmergify[bot]
authored
Fix #3574 and support resolve in explicit records (#3750)
* Fix #3574 and support resolve in explicit records * render shouldn't fail, added tests * Improved comments * Remove unused language extensions * 8.10 and 9.0 fixes and separate collect names into it's own rule * fix flags and add Resolve module haddock * better tests * works for all ghc versions * Fix flags * ignore incomplete record updates in explicit record fields --------- Co-authored-by: Michael Peyton Jones <me@michaelpj.com> Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent e516937 commit 90d71ce

File tree

9 files changed

+293
-147
lines changed

9 files changed

+293
-147
lines changed

ghcide/src/Development/IDE/GHC/Orphans.hs

+7-1
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@ import Data.Text (unpack)
2323
#if !MIN_VERSION_ghc(9,0,0)
2424
import Bag
2525
import ByteCodeTypes
26-
import GhcPlugins
26+
import GhcPlugins hiding (UniqFM)
2727
import qualified StringBuffer as SB
2828
import Unique (getKey)
2929
#endif
@@ -252,5 +252,11 @@ instance NFData HomeModLinkable where
252252
instance NFData (HsExpr (GhcPass Renamed)) where
253253
rnf = rwhnf
254254

255+
instance NFData (Pat (GhcPass Renamed)) where
256+
rnf = rwhnf
257+
255258
instance NFData Extension where
256259
rnf = rwhnf
260+
261+
instance NFData (UniqFM Name [Name]) where
262+
rnf (ufmToIntMap -> m) = rnf m

hls-plugin-api/src/Ide/Plugin/Resolve.hs

+12
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,18 @@
66
{-# LANGUAGE OverloadedStrings #-}
77
{-# LANGUAGE RankNTypes #-}
88
{-# LANGUAGE ScopedTypeVariables #-}
9+
{-| This module currently includes helper functions to provide fallback support
10+
to code actions that use resolve in HLS. The difference between the two
11+
functions for code actions that don't support resolve is that
12+
mkCodeActionHandlerWithResolve will immediately resolve your code action before
13+
sending it on to the client, while mkCodeActionWithResolveAndCommand will turn
14+
your resolve into a command.
15+
16+
General support for resolve in HLS can be used with mkResolveHandler from
17+
Ide.Types. Resolve theoretically should allow us to delay computation of parts
18+
of the request till the client needs it, allowing us to answer requests faster
19+
and with less resource usage.
20+
-}
921
module Ide.Plugin.Resolve
1022
(mkCodeActionHandlerWithResolve,
1123
mkCodeActionWithResolveAndCommand) where

plugins/hls-explicit-record-fields-plugin/hls-explicit-record-fields-plugin.cabal

+11
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,11 @@ source-repository head
1919
type: git
2020
location: https://github.com/haskell/haskell-language-server
2121

22+
flag pedantic
23+
description: Enable -Werror
24+
default: False
25+
manual: True
26+
2227
common warnings
2328
ghc-options: -Wall
2429

@@ -29,6 +34,7 @@ library
2934
-- other-extensions:
3035
build-depends:
3136
, base >=4.12 && <5
37+
, ghc
3238
, ghcide == 2.1.0.0
3339
, hls-plugin-api == 2.1.0.0
3440
, lsp
@@ -40,9 +46,14 @@ library
4046
, ghc-boot-th
4147
, unordered-containers
4248
, containers
49+
, aeson
4350
hs-source-dirs: src
4451
default-language: Haskell2010
4552

53+
if flag(pedantic)
54+
ghc-options: -Werror
55+
-Wwarn=incomplete-record-updates
56+
4657
test-suite tests
4758
import: warnings
4859
default-language: Haskell2010

plugins/hls-explicit-record-fields-plugin/src/Ide/Plugin/ExplicitFields.hs

+164-140
Large diffs are not rendered by default.

plugins/hls-explicit-record-fields-plugin/test/Main.hs

+11-6
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,6 @@ import qualified Ide.Plugin.ExplicitFields as ExplicitFields
1111
import System.FilePath ((<.>), (</>))
1212
import Test.Hls
1313

14-
1514
main :: IO ()
1615
main = defaultTestRunner test
1716

@@ -27,6 +26,8 @@ test = testGroup "explicit-fields"
2726
, mkTest "WithExplicitBind" "WithExplicitBind" 12 10 12 32
2827
, mkTest "Mixed" "Mixed" 14 10 14 37
2928
, mkTest "Construction" "Construction" 16 5 16 15
29+
, mkTest "HsExpanded1" "HsExpanded1" 17 10 17 20
30+
, mkTest "HsExpanded2" "HsExpanded2" 23 10 23 22
3031
, mkTestNoAction "ExplicitBinds" "ExplicitBinds" 11 10 11 52
3132
, mkTestNoAction "Puns" "Puns" 12 10 12 31
3233
, mkTestNoAction "Infix" "Infix" 11 11 11 31
@@ -41,18 +42,22 @@ mkTestNoAction title fp x1 y1 x2 y2 =
4142
actions <- getExplicitFieldsActions doc x1 y1 x2 y2
4243
liftIO $ actions @?= []
4344

44-
mkTest :: TestName -> FilePath -> UInt -> UInt -> UInt -> UInt -> TestTree
45-
mkTest title fp x1 y1 x2 y2 =
46-
goldenWithHaskellDoc plugin title testDataDir fp "expected" "hs" $ \doc -> do
47-
(act:_) <- getExplicitFieldsActions doc x1 y1 x2 y2
45+
mkTestWithCount :: Int -> TestName -> FilePath -> UInt -> UInt -> UInt -> UInt -> TestTree
46+
mkTestWithCount cnt title fp x1 y1 x2 y2 =
47+
goldenWithHaskellAndCaps codeActionResolveCaps plugin title testDataDir fp "expected" "hs" $ \doc -> do
48+
acts@(act:_) <- getExplicitFieldsActions doc x1 y1 x2 y2
49+
liftIO $ length acts @?= cnt
4850
executeCodeAction act
4951

52+
mkTest :: TestName -> FilePath -> UInt -> UInt -> UInt -> UInt -> TestTree
53+
mkTest = mkTestWithCount 1
54+
5055
getExplicitFieldsActions
5156
:: TextDocumentIdentifier
5257
-> UInt -> UInt -> UInt -> UInt
5358
-> Session [CodeAction]
5459
getExplicitFieldsActions doc x1 y1 x2 y2 =
55-
findExplicitFieldsAction <$> getCodeActions doc range
60+
findExplicitFieldsAction <$> getAndResolveCodeActions doc range
5661
where
5762
range = Range (Position x1 y1) (Position x2 y2)
5863

Original file line numberDiff line numberDiff line change
@@ -0,0 +1,19 @@
1+
{-# LANGUAGE RecordWildCards #-}
2+
{-# LANGUAGE RebindableSyntax #-}
3+
{-# LANGUAGE NamedFieldPuns #-}
4+
5+
module HsExpanded1 where
6+
import Prelude
7+
8+
ifThenElse :: Int -> Int -> Int -> Int
9+
ifThenElse x y z = x + y + z
10+
11+
data MyRec = MyRec
12+
{ foo :: Int }
13+
14+
myRecExample = MyRec 5
15+
16+
convertMe :: Int
17+
convertMe =
18+
if (let MyRec {foo} = myRecExample
19+
in foo) then 1 else 2
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,19 @@
1+
{-# LANGUAGE RecordWildCards #-}
2+
{-# LANGUAGE RebindableSyntax #-}
3+
{-# LANGUAGE NamedFieldPuns #-}
4+
5+
module HsExpanded1 where
6+
import Prelude
7+
8+
ifThenElse :: Int -> Int -> Int -> Int
9+
ifThenElse x y z = x + y + z
10+
11+
data MyRec = MyRec
12+
{ foo :: Int }
13+
14+
myRecExample = MyRec 5
15+
16+
convertMe :: Int
17+
convertMe =
18+
if (let MyRec {..} = myRecExample
19+
in foo) then 1 else 2
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,25 @@
1+
{-# LANGUAGE RecordWildCards #-}
2+
{-# LANGUAGE RebindableSyntax #-}
3+
{-# LANGUAGE NamedFieldPuns #-}
4+
5+
module HsExpanded2 where
6+
import Prelude
7+
8+
ifThenElse :: Int -> Int -> Int -> Int
9+
ifThenElse x y z = x + y + z
10+
11+
data MyRec = MyRec
12+
{ foo :: Int }
13+
14+
data YourRec = YourRec
15+
{ bar :: Int }
16+
17+
myRecExample = MyRec 5
18+
19+
yourRecExample = YourRec 3
20+
21+
convertMe :: Int
22+
convertMe =
23+
if (let MyRec {..} = myRecExample
24+
YourRec {bar} = yourRecExample
25+
in bar) then 1 else 2
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,25 @@
1+
{-# LANGUAGE RecordWildCards #-}
2+
{-# LANGUAGE RebindableSyntax #-}
3+
{-# LANGUAGE NamedFieldPuns #-}
4+
5+
module HsExpanded2 where
6+
import Prelude
7+
8+
ifThenElse :: Int -> Int -> Int -> Int
9+
ifThenElse x y z = x + y + z
10+
11+
data MyRec = MyRec
12+
{ foo :: Int }
13+
14+
data YourRec = YourRec
15+
{ bar :: Int }
16+
17+
myRecExample = MyRec 5
18+
19+
yourRecExample = YourRec 3
20+
21+
convertMe :: Int
22+
convertMe =
23+
if (let MyRec {..} = myRecExample
24+
YourRec {..} = yourRecExample
25+
in bar) then 1 else 2

0 commit comments

Comments
 (0)