Skip to content

Commit 2ad9eb0

Browse files
Fix the bug that generating comments would duplicate existing comments (#1233)
* Fix duplicating existed comments * Factorize and do the same to genForRecord * Remove unused pragmas * Remove unused identifiers * Fix code action positions in tests * Use new rule: GetAnnotatedParsedSource Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent a44f4b4 commit 2ad9eb0

File tree

6 files changed

+28
-14
lines changed

6 files changed

+28
-14
lines changed

plugins/hls-haddock-comments-plugin/src/Ide/Plugin/HaddockComments.hs

Lines changed: 20 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,17 +1,19 @@
11
{-# LANGUAGE ExistentialQuantification #-}
2+
{-# LANGUAGE FlexibleContexts #-}
23
{-# LANGUAGE NamedFieldPuns #-}
34
{-# LANGUAGE OverloadedStrings #-}
45
{-# LANGUAGE RecordWildCards #-}
56
{-# LANGUAGE ViewPatterns #-}
67

7-
module Ide.Plugin.HaddockComments where
8+
module Ide.Plugin.HaddockComments (descriptor) where
89

910
import Control.Monad (join)
1011
import qualified Data.HashMap.Strict as HashMap
1112
import qualified Data.Map as Map
1213
import qualified Data.Text as T
1314
import Development.IDE
1415
import Development.IDE.GHC.Compat
16+
import Development.IDE.GHC.ExactPrint (GetAnnotatedParsedSource (..), annsA, astA)
1517
import Ide.Types
1618
import Language.Haskell.GHC.ExactPrint
1719
import Language.Haskell.GHC.ExactPrint.Types hiding (GhcPs)
@@ -25,17 +27,14 @@ descriptor plId =
2527
{ pluginCodeActionProvider = Just codeActionProvider
2628
}
2729

28-
haddockCommentsId :: CommandId
29-
haddockCommentsId = "HaddockCommentsCommand"
30-
3130
codeActionProvider :: CodeActionProvider IdeState
3231
codeActionProvider _lspFuncs ideState _pId (TextDocumentIdentifier uri) range CodeActionContext {_diagnostics = List diags} =
3332
do
3433
let noErr = and $ (/= Just DsError) . _severity <$> diags
3534
nfp = uriToNormalizedFilePath $ toNormalizedUri uri
36-
(join -> pm) <- runAction "HaddockComments.GetParsedModule" ideState $ use GetParsedModule `traverse` nfp
37-
let locDecls = hsmodDecls . unLoc . pm_parsed_source <$> pm
38-
anns = relativiseApiAnns <$> (pm_parsed_source <$> pm) <*> (pm_annotations <$> pm)
35+
(join -> pm) <- runAction "HaddockComments.GetAnnotatedParsedSource" ideState $ use GetAnnotatedParsedSource `traverse` nfp
36+
let locDecls = hsmodDecls . unLoc . astA <$> pm
37+
anns = annsA <$> pm
3938
edits = [runGenComments gen locDecls anns range | noErr, gen <- genList]
4039
return $ Right $ List [CACodeAction $ toAction title uri edit | (Just (title, edit)) <- edits]
4140

@@ -46,13 +45,16 @@ genList =
4645
]
4746

4847
-----------------------------------------------------------------------------
48+
49+
-- | Defines how to generate haddock comments by tweaking annotations of AST
4950
data GenComments = forall a.
5051
GenComments
5152
{ title :: T.Text,
5253
fromDecl :: HsDecl GhcPs -> Maybe a,
5354
collectKeys :: a -> [AnnKey],
5455
isFresh :: Annotation -> Bool,
55-
updateAnn :: Annotation -> Annotation
56+
updateAnn :: Annotation -> Annotation,
57+
updateDeclAnn :: Annotation -> Annotation
5658
}
5759

5860
runGenComments :: GenComments -> Maybe [LHsDecl GhcPs] -> Maybe Anns -> Range -> Maybe (T.Text, TextEdit)
@@ -63,7 +65,8 @@ runGenComments GenComments {..} mLocDecls mAnns range
6365
annKeys <- collectKeys x,
6466
not $ null annKeys,
6567
and $ maybe False isFresh . flip Map.lookup anns <$> annKeys,
66-
anns' <- foldr (Map.adjust updateAnn) anns annKeys,
68+
declKey <- mkAnnKey locDecl,
69+
anns' <- Map.adjust updateDeclAnn declKey $ foldr (Map.adjust updateAnn) anns annKeys,
6770
Just range' <- toRange src,
6871
result <- T.strip . T.pack $ exactPrint locDecl anns' =
6972
Just (title, TextEdit range' result)
@@ -80,9 +83,9 @@ genForSig = GenComments {..}
8083
fromDecl _ = Nothing
8184

8285
updateAnn x = x {annEntryDelta = DP (0, 1), annsDP = dp}
86+
updateDeclAnn = cleanPriorComments
8387

8488
isFresh Ann {annsDP} = null [() | (AnnComment _, _) <- annsDP]
85-
8689
collectKeys = keyFromTyVar 0
8790

8891
comment = mkComment "-- ^ " noSrcSpan
@@ -98,6 +101,7 @@ genForRecord = GenComments {..}
98101
fromDecl _ = Nothing
99102

100103
updateAnn x = x {annEntryDelta = DP (1, 2), annPriorComments = [(comment, DP (1, 2))]}
104+
updateDeclAnn = cleanPriorComments
101105

102106
isFresh Ann {annPriorComments} = null annPriorComments
103107

@@ -120,14 +124,18 @@ toAction title uri edit = CodeAction {..}
120124

121125
toRange :: SrcSpan -> Maybe Range
122126
toRange src
123-
| (RealSrcSpan span) <- src,
124-
range' <- realSrcSpanToRange span =
127+
| (RealSrcSpan s) <- src,
128+
range' <- realSrcSpanToRange s =
125129
Just range'
126130
| otherwise = Nothing
127131

128132
isIntersectWith :: Range -> SrcSpan -> Bool
129133
isIntersectWith Range {_start, _end} x = isInsideSrcSpan _start x || isInsideSrcSpan _end x
130134

135+
-- clean prior comments, since src span we get from 'LHsDecl' does not include them
136+
cleanPriorComments :: Annotation -> Annotation
137+
cleanPriorComments x = x {annPriorComments = []}
138+
131139
-----------------------------------------------------------------------------
132140

133141
keyFromTyVar :: Int -> LHsType GhcPs -> [AnnKey]

test/functional/HaddockComments.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ tests =
2828
"haddock comments"
2929
[ goldenTest "HigherRankFunction" Signature 4 6,
3030
goldenTest "KindSigFunction" Signature 9 10,
31-
goldenTest "MultivariateFunction" Signature 2 8,
31+
goldenTest "MultivariateFunction" Signature 4 8,
3232
goldenTest "QualFunction" Signature 2 10,
3333
goldenTest "Record" Record 7 2,
3434
expectedNothing "ConstFunction" Signature 2 2,
@@ -37,7 +37,7 @@ tests =
3737
]
3838

3939
goldenTest :: FilePath -> GenCommentsType -> Int -> Int -> TestTree
40-
goldenTest fp (toTitle -> expectedTitle) l c = goldenVsStringDiff fp goldenGitDiff goldenFilePath $
40+
goldenTest fp (toTitle -> expectedTitle) l c = goldenVsStringDiff (fp <> " (golden)") goldenGitDiff goldenFilePath $
4141
runSession hlsCommand fullCaps haddockCommentsPath $ do
4242
doc <- openDoc hsFilePath "haskell"
4343
_ <- waitForDiagnostics

test/testdata/haddockComments/MultivariateFunction.expected.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,7 @@
11
module MultivariateFunction where
22

3+
-- | some
4+
-- docs
35
f :: a -- ^
46
-> b -- ^
57
-> c -- ^
Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,6 @@
11
module MultivariateFunction where
22

3+
-- | some
4+
-- docs
35
f :: a -> b -> c -> d -> e -> f -> g -> g
46
f _ _ _ _ _ _ x = x

test/testdata/haddockComments/Record.expected.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
module Record where
22

3+
-- | A record
34
data Record a b c d e f
45
= RecordA
56
{

test/testdata/haddockComments/Record.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
module Record where
22

3+
-- | A record
34
data Record a b c d e f
45
= RecordA
56
{ a :: a,

0 commit comments

Comments
 (0)