1
1
{-# LANGUAGE ExistentialQuantification #-}
2
+ {-# LANGUAGE FlexibleContexts #-}
2
3
{-# LANGUAGE NamedFieldPuns #-}
3
4
{-# LANGUAGE OverloadedStrings #-}
4
5
{-# LANGUAGE RecordWildCards #-}
5
6
{-# LANGUAGE ViewPatterns #-}
6
7
7
- module Ide.Plugin.HaddockComments where
8
+ module Ide.Plugin.HaddockComments ( descriptor ) where
8
9
9
10
import Control.Monad (join )
10
11
import qualified Data.HashMap.Strict as HashMap
11
12
import qualified Data.Map as Map
12
13
import qualified Data.Text as T
13
14
import Development.IDE
14
15
import Development.IDE.GHC.Compat
16
+ import Development.IDE.GHC.ExactPrint (GetAnnotatedParsedSource (.. ), annsA , astA )
15
17
import Ide.Types
16
18
import Language.Haskell.GHC.ExactPrint
17
19
import Language.Haskell.GHC.ExactPrint.Types hiding (GhcPs )
@@ -25,17 +27,14 @@ descriptor plId =
25
27
{ pluginCodeActionProvider = Just codeActionProvider
26
28
}
27
29
28
- haddockCommentsId :: CommandId
29
- haddockCommentsId = " HaddockCommentsCommand"
30
-
31
30
codeActionProvider :: CodeActionProvider IdeState
32
31
codeActionProvider _lspFuncs ideState _pId (TextDocumentIdentifier uri) range CodeActionContext {_diagnostics = List diags} =
33
32
do
34
33
let noErr = and $ (/= Just DsError ) . _severity <$> diags
35
34
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
39
38
edits = [runGenComments gen locDecls anns range | noErr, gen <- genList]
40
39
return $ Right $ List [CACodeAction $ toAction title uri edit | (Just (title, edit)) <- edits]
41
40
@@ -46,13 +45,16 @@ genList =
46
45
]
47
46
48
47
-----------------------------------------------------------------------------
48
+
49
+ -- | Defines how to generate haddock comments by tweaking annotations of AST
49
50
data GenComments = forall a .
50
51
GenComments
51
52
{ title :: T. Text ,
52
53
fromDecl :: HsDecl GhcPs -> Maybe a ,
53
54
collectKeys :: a -> [AnnKey ],
54
55
isFresh :: Annotation -> Bool ,
55
- updateAnn :: Annotation -> Annotation
56
+ updateAnn :: Annotation -> Annotation ,
57
+ updateDeclAnn :: Annotation -> Annotation
56
58
}
57
59
58
60
runGenComments :: GenComments -> Maybe [LHsDecl GhcPs ] -> Maybe Anns -> Range -> Maybe (T. Text , TextEdit )
@@ -63,7 +65,8 @@ runGenComments GenComments {..} mLocDecls mAnns range
63
65
annKeys <- collectKeys x,
64
66
not $ null annKeys,
65
67
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,
67
70
Just range' <- toRange src,
68
71
result <- T. strip . T. pack $ exactPrint locDecl anns' =
69
72
Just (title, TextEdit range' result)
@@ -80,9 +83,9 @@ genForSig = GenComments {..}
80
83
fromDecl _ = Nothing
81
84
82
85
updateAnn x = x {annEntryDelta = DP (0 , 1 ), annsDP = dp}
86
+ updateDeclAnn = cleanPriorComments
83
87
84
88
isFresh Ann {annsDP} = null [() | (AnnComment _, _) <- annsDP]
85
-
86
89
collectKeys = keyFromTyVar 0
87
90
88
91
comment = mkComment " -- ^ " noSrcSpan
@@ -98,6 +101,7 @@ genForRecord = GenComments {..}
98
101
fromDecl _ = Nothing
99
102
100
103
updateAnn x = x {annEntryDelta = DP (1 , 2 ), annPriorComments = [(comment, DP (1 , 2 ))]}
104
+ updateDeclAnn = cleanPriorComments
101
105
102
106
isFresh Ann {annPriorComments} = null annPriorComments
103
107
@@ -120,14 +124,18 @@ toAction title uri edit = CodeAction {..}
120
124
121
125
toRange :: SrcSpan -> Maybe Range
122
126
toRange src
123
- | (RealSrcSpan span ) <- src,
124
- range' <- realSrcSpanToRange span =
127
+ | (RealSrcSpan s ) <- src,
128
+ range' <- realSrcSpanToRange s =
125
129
Just range'
126
130
| otherwise = Nothing
127
131
128
132
isIntersectWith :: Range -> SrcSpan -> Bool
129
133
isIntersectWith Range {_start, _end} x = isInsideSrcSpan _start x || isInsideSrcSpan _end x
130
134
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
+
131
139
-----------------------------------------------------------------------------
132
140
133
141
keyFromTyVar :: Int -> LHsType GhcPs -> [AnnKey ]
0 commit comments