@@ -8,7 +8,7 @@ module Ide.Plugin.Class.CodeLens where
8
8
import Control.Lens ((^.) )
9
9
import Control.Monad.IO.Class (liftIO )
10
10
import Data.Aeson
11
- import Data.Maybe (mapMaybe )
11
+ import Data.Maybe (mapMaybe , maybeToList )
12
12
import qualified Data.Text as T
13
13
import Development.IDE
14
14
import Development.IDE.GHC.Compat
@@ -32,7 +32,8 @@ codeLens state plId CodeLensParams{..} = do
32
32
$ runAction " classplugin.TypeCheck" state
33
33
$ use TypeCheck nfp
34
34
35
- InstanceBindTypeSigsResult binds <-
35
+ -- All instance binds
36
+ InstanceBindTypeSigsResult allBinds <-
36
37
handleMaybeM " Unable to get InstanceBindTypeSigsResult"
37
38
$ liftIO
38
39
$ runAction " classplugin.GetInstanceBindTypeSigs" state
@@ -42,29 +43,39 @@ codeLens state plId CodeLensParams{..} = do
42
43
43
44
let (hsGroup, _, _, _) = tmrRenamed tmr
44
45
tycls = hs_tyclds hsGroup
45
- -- class instance decls
46
- insts = mapMaybe (getClsInstD . unLoc) $ concatMap group_instds tycls
47
- -- Declared instance methods without signatures
48
- bindInfos = concatMap getBindSpanWithoutSig insts
49
- targetSigs = matchBind bindInfos binds
50
- codeLens =
51
- (\ x@ (range, title) ->
52
- generateLens plId range title
46
+ -- declared instance methods without signatures
47
+ bindInfos = [ bind
48
+ | instds <- map group_instds tycls -- class instance decls
49
+ , instd <- instds
50
+ , inst <- maybeToList $ getClsInstD (unLoc instd)
51
+ , bind <- getBindSpanWithoutSig inst
52
+ ]
53
+ targetSigs = matchBind bindInfos allBinds
54
+ makeLens (range, title) =
55
+ generateLens plId range title
53
56
$ workspaceEdit pragmaInsertion
54
- $ makeEdit x
55
- ) <$> mapMaybe getRangeWithSig targetSigs
57
+ $ makeEdit range title
58
+ codeLens = makeLens <$> mapMaybe getRangeWithSig targetSigs
56
59
57
60
pure $ List codeLens
58
61
where
59
62
uri = _textDocument ^. J. uri
60
63
61
64
-- Match Binds with their signatures
65
+ -- We try to give every `InstanceBindTypeSig` a `SrcSpan`,
66
+ -- hence we can display signatures for `InstanceBindTypeSig` with span later.
62
67
matchBind :: [BindInfo ] -> [InstanceBindTypeSig ] -> [InstanceBindTypeSig ]
63
- matchBind binds = map go
68
+ matchBind existedBinds allBindWithSigs =
69
+ [foldl go bindSig existedBinds | bindSig <- allBindWithSigs]
64
70
where
71
+ -- | The `bindDefSpan` of the bind is `Nothing` before,
72
+ -- we update it with the span where binding occurs.
73
+ -- Hence, we can infer the place to display the signature later.
74
+ update :: InstanceBindTypeSig -> SrcSpan -> InstanceBindTypeSig
65
75
update bind sp = bind {bindDefSpan = Just sp}
66
- go sig = foldl go' sig binds
67
- go' bindSig bind = case (srcSpanToRange . bindNameSpan) bind of
76
+
77
+ go :: InstanceBindTypeSig -> BindInfo -> InstanceBindTypeSig
78
+ go bindSig bind = case (srcSpanToRange . bindNameSpan) bind of
68
79
Nothing -> bindSig
69
80
Just range ->
70
81
if inRange range (getSrcSpan $ bindName bindSig)
@@ -109,23 +120,12 @@ codeLens state plId CodeLensParams{..} = do
109
120
let cmd = mkLspCommand plId typeLensCommandId title (Just [toJSON edit])
110
121
in CodeLens range (Just cmd) Nothing
111
122
112
- makeEdit :: (Range , T. Text ) -> [TextEdit ]
113
- makeEdit (range, bind)
114
- | indentSize > maxSize =
115
- [TextEdit (insertRange (indentSize - 1 )) -- minus one to remove the leading space
116
- (" \n "
117
- <> T. replicate defaultIndent " "
118
- <> bind
119
- <> " \n "
120
- <> T. replicate (defaultIndent - 1 ) " " )]
121
- | otherwise = [TextEdit (insertRange 0 ) (T. replicate indentSize " " <> bind <> " \n " )]
122
- where
123
- startOfLine = Position (_line (range ^. J. start))
124
- insertRange c = Range (startOfLine c) (startOfLine c)
125
- maxSize :: Int
126
- maxSize = 18 -- Length of the shortest instance like `instance X A where`
127
- indentSize :: Num a => a
128
- indentSize = fromIntegral $ _character $ range ^. J. start
123
+ makeEdit :: Range -> T. Text -> [TextEdit ]
124
+ makeEdit range bind =
125
+ let startPos = range ^. J. start
126
+ insertChar = startPos ^. J. character
127
+ insertRange = Range startPos startPos
128
+ in [TextEdit insertRange (bind <> " \n " <> T. replicate (fromIntegral insertChar) " " )]
129
129
130
130
codeLensCommandHandler :: CommandFunction IdeState WorkspaceEdit
131
131
codeLensCommandHandler _ wedit = do
0 commit comments