@@ -12,26 +12,33 @@ import BooleanFormula
1212import Class
1313import ConLike
1414import Control.Applicative
15- import Control.Lens hiding (List )
15+ import Control.Lens hiding (List , use )
1616import Control.Monad
1717import Data.Aeson
1818import Data.Char
19+ import qualified Data.HashMap.Strict as H
1920import Data.List
2021import qualified Data.Map.Strict as Map
2122import Data.Maybe
2223import qualified Data.Text as T
2324import Development.IDE
24- import Development.IDE.GHC.Compat
25+ import Development.IDE.Core.PositionMapping (fromCurrentRange , toCurrentRange )
26+ import Development.IDE.GHC.Compat hiding (getLoc )
2527import Development.IDE.Spans.AtPoint
2628import qualified GHC.Generics as Generics
27- import GhcPlugins hiding (Var , (<>) )
29+ import GhcPlugins hiding (Var , getLoc , (<>) )
2830import Ide.Plugin
31+ import Ide.PluginUtils
2932import Ide.Types
33+ import Language.Haskell.GHC.ExactPrint
34+ import Language.Haskell.GHC.ExactPrint.Parsers (parseDecl )
35+ import Language.Haskell.GHC.ExactPrint.Types hiding (GhcPs , Parens )
36+ import Language.Haskell.LSP.Core
3037import Language.Haskell.LSP.Types
3138import qualified Language.Haskell.LSP.Types.Lens as J
39+ import SrcLoc
3240import TcEnv
3341import TcRnMonad
34- import qualified Data.HashMap.Strict as H
3542
3643descriptor :: PluginId -> PluginDescriptor
3744descriptor plId = (defaultPluginDescriptor plId)
@@ -40,36 +47,72 @@ descriptor plId = (defaultPluginDescriptor plId)
4047 }
4148
4249commands :: [PluginCommand ]
43- commands = [ PluginCommand " addMethodPlaceholders" " add placeholders for minimal methods" addMethodPlaceholders
44- ]
50+ commands
51+ = [ PluginCommand " addMinimalMethodPlaceholders" " add placeholders for minimal methods" addMethodPlaceholders
52+ ]
4553
4654-- | Parameter for the addMethods PluginCommand.
47- data AddMethodsParams = AddMethodsParams
55+ data AddMinimalMethodsParams = AddMinimalMethodsParams
4856 { uri :: Uri
4957 , range :: Range
5058 , methodGroup :: List T. Text
5159 }
5260 deriving (Show , Eq , Generics.Generic , ToJSON , FromJSON )
5361
54- addMethodPlaceholders :: CommandFunction AddMethodsParams
55- addMethodPlaceholders _ _ AddMethodsParams {.. } = pure (Right Null , Just (WorkspaceApplyEdit , ApplyWorkspaceEditParams workspaceEdit))
62+ addMethodPlaceholders :: CommandFunction AddMinimalMethodsParams
63+ addMethodPlaceholders lf state AddMinimalMethodsParams {.. } = do
64+ Just pm <- runAction " classplugin" state $ use GetParsedModule docPath
65+ let
66+ ps = pm_parsed_source pm
67+ anns = relativiseApiAnns ps (pm_annotations pm)
68+ old = T. pack $ exactPrint ps anns
69+
70+ Just (hsc_dflags . hscEnv -> df) <- runAction " classplugin" state $ use GhcSessionDeps docPath
71+ let
72+ Right (List (unzip -> (mAnns, mDecls))) = traverse (makeMethodDecl df) methodGroup
73+ (ps', (anns', _), _) = runTransform (mergeAnns (mergeAnnList mAnns) anns) (addMethodDecls ps mDecls)
74+ new = T. pack $ exactPrint ps' anns'
75+
76+ pure (Right Null , Just (WorkspaceApplyEdit , ApplyWorkspaceEditParams (workspaceEdit caps old new)))
5677 where
57- workspaceEdit
58- = WorkspaceEdit
59- (Just (H. singleton uri textEdits))
60- Nothing
61-
62- textEdits
63- = List
64- [ TextEdit (Range pos pos) $ " \n " <> methodText
65- ]
66-
67- methodText
68- = mconcat
69- . intersperse " \n "
70- . fmap (\ n -> T. replicate indentSize " " <> toMethodName n <> " = _" )
71- . unList
72- $ methodGroup
78+ caps = clientCapabilities lf
79+ Just docPath = uriToNormalizedFilePath $ toNormalizedUri uri
80+
81+ indent = 2
82+
83+ makeMethodDecl df mName = do
84+ (ann, d) <- parseDecl df (T. unpack mName) . T. unpack $ toMethodName mName <> " = _"
85+ pure (setPrecedingLines d 1 indent ann, d)
86+
87+ addMethodDecls :: ParsedSource -> [LHsDecl GhcPs ] -> Transform (Located (HsModule GhcPs ))
88+ addMethodDecls ps mDecls = do
89+ d <- findInstDecl ps
90+ newSpan <- uniqueSrcSpanT
91+ let
92+ newAnnKey = AnnKey newSpan (CN " HsValBinds" )
93+ addWhere mkds@ (Map. lookup (mkAnnKey d) -> Just ann)
94+ = Map. insert newAnnKey ann2 mkds2
95+ where
96+ annKey = mkAnnKey d
97+ ann1 = ann
98+ { annsDP = annsDP ann ++ [(G AnnWhere , DP (0 , 1 ))]
99+ , annCapturedSpan = Just newAnnKey
100+ , annSortKey = Just (fmap getLoc mDecls)
101+ }
102+ mkds2 = Map. insert annKey ann1 mkds
103+ ann2 = annNone
104+ { annEntryDelta = DP (1 , 2 )
105+ }
106+ addWhere _ = panic " Ide.Plugin.Class.addMethodPlaceholder"
107+ modifyAnnsT addWhere
108+ modifyAnnsT (captureOrderAnnKey newAnnKey mDecls)
109+ foldM (insertAfter d) ps (reverse mDecls)
110+
111+ findInstDecl :: ParsedSource -> Transform (LHsDecl GhcPs )
112+ findInstDecl ps = head . filter (containRange range . getLoc) <$> hsDecls ps
113+
114+ workspaceEdit caps old new
115+ = diffText caps (uri, old) new IncludeDeletions
73116
74117 toMethodName n
75118 | Just (h, _) <- T. uncons n
@@ -78,65 +121,83 @@ addMethodPlaceholders _ _ AddMethodsParams{..} = pure (Right Null, Just (Workspa
78121 | otherwise
79122 = n
80123
81- pos = range ^. J. end
82- indentSize = range ^. J. start . J. character + 2
83-
84124-- | This implementation is extremely ad-hoc in a sense that
85125-- 1. sensitive to the format of diagnostic messages from GHC
86126-- 2. pattern matches are not exhaustive
87127codeAction :: CodeActionProvider
88- codeAction _ state plId docId _ ctx = do
89- let Just docPath = docId ^. J. uri & uriToFilePath <&> toNormalizedFilePath
90- actions <- join <$> mapM (mkActions docPath) methodDiags
128+ codeAction _ state plId (TextDocumentIdentifier uri) _ CodeActionContext { _diagnostics = List diags } = do
129+ actions <- join <$> mapM mkActions methodDiags
91130 pure . Right . List $ actions
92131 where
93- ghcDiags = filter (\ d -> d ^. J. source == Just " typecheck" ) . unList $ ctx ^. J. diagnostics
94- methodDiags = filter (\ d -> isClassMethodWarning (d ^. J. message)) ghcDiags
132+ Just docPath = uriToNormalizedFilePath $ toNormalizedUri uri
95133
96- ghostSpan = realSrcLocSpan $ mkRealSrcLoc (fsLit " <haskell-language-sever>" ) 1 1
134+ ghcDiags = filter (\ d -> d ^. J. source == Just " typecheck" ) diags
135+ methodDiags = filter (\ d -> isClassMethodWarning (d ^. J. message)) ghcDiags
97136
98- mkAction range methodGroup
99- = codeAction <$> mkLspCommand plId " addMethodPlaceholders" title (Just cmdParams)
137+ mkActions diag = do
138+ ident <- findClassIdentifier range
139+ cls <- findClassFromIdentifier ident
140+ traverse mkAction . minDefToMethodGroups . classMinimalDef $ cls
100141 where
101- title = " Add placeholders for "
102- <> mconcat (intersperse " , " (fmap (\ m -> " ‘" <> m <> " ’" ) methodGroup))
103- cmdParams = [toJSON (AddMethodsParams (docId ^. J. uri) range (List methodGroup))]
142+ range = diag ^. J. range
104143
105- codeAction cmd
106- = CACodeAction
107- $ CodeAction title (Just CodeActionQuickFix ) (Just (List [] )) Nothing (Just cmd)
144+ mkAction methodGroup
145+ = mkCodeAction title
146+ <$> mkLspCommand plId " addMinimalMethodPlaceholders" title (Just cmdParams)
147+ where
148+ title = mkTitle methodGroup
149+ cmdParams = mkCmdParams methodGroup
108150
109- mkActions docPath d = do
110- Just (hieAst -> hf, _) <- runAction " classplugin" state $ useWithStale GetHieAst docPath
111- let
112- [([[Right name]], range)]
113- = pointCommand hf (d ^. J. range . J. start & J. character -~ 1 )
114- $ \ n ->
115- ( Map. keys . Map. filter (isNothing . identType) . nodeIdentifiers . nodeInfo <$> nodeChildren n
116- , realSrcSpanToRange (nodeSpan n)
117- )
151+ mkTitle methodGroup
152+ = " Add placeholders for "
153+ <> mconcat (intersperse " , " (fmap (\ m -> " '" <> m <> " '" ) methodGroup))
154+
155+ mkCmdParams methodGroup = [toJSON (AddMinimalMethodsParams uri range (List methodGroup))]
156+
157+ mkCodeAction title
158+ = CACodeAction
159+ . CodeAction title (Just CodeActionQuickFix ) (Just (List [] )) Nothing
160+ . Just
161+
162+ findClassIdentifier :: Range -> IO Identifier
163+ findClassIdentifier range = do
164+ Just (hieAst -> hf, pmap) <- runAction " classplugin" state $ useWithStale GetHieAst docPath
165+ pure
166+ $ head . head
167+ $ pointCommand hf (fromJust (fromCurrentRange pmap range) ^. J. start & J. character -~ 1 )
168+ ( (Map. keys . Map. filter isClassNodeIdentifier . nodeIdentifiers . nodeInfo)
169+ <=< nodeChildren
170+ )
171+
172+ findClassFromIdentifier :: Identifier -> IO Class
173+ findClassFromIdentifier (Right name) = do
118174 Just (hscEnv -> hscenv, _) <- runAction " classplugin" state $ useWithStale GhcSessionDeps docPath
119175 Just (tmrTypechecked -> thisMod, _) <- runAction " classplugin" state $ useWithStale TypeCheck docPath
120176 (_, Just cls) <- initTcWithGbl hscenv thisMod ghostSpan $ do
121177 tcthing <- tcLookup name
122178 case tcthing of
123179 AGlobal (AConLike (RealDataCon con))
124180 | Just cls <- tyConClass_maybe (dataConOrigTyCon con) -> pure cls
125- _ -> panic " Ide.Plugin.Class.mkActions"
126- let
127- minDef = classMinimalDef cls
128- traverse (mkAction range) (minDefToMethodGroups minDef)
181+ _ -> panic " Ide.Plugin.Class.findClassFromIdentifier"
182+ pure cls
183+ findClassFromIdentifier (Left _) = panic " Ide.Plugin.Class.findClassIdentifier"
184+
185+ ghostSpan :: RealSrcSpan
186+ ghostSpan = realSrcLocSpan $ mkRealSrcLoc (fsLit " <haskell-language-sever>" ) 1 1
187+
188+ containRange :: Range -> SrcSpan -> Bool
189+ containRange range x = isInsideSrcSpan (range ^. J. start) x || isInsideSrcSpan (range ^. J. end) x
129190
130- unList :: List a -> [ a ]
131- unList ( List xs) = xs
191+ isClassNodeIdentifier :: IdentifierDetails a -> Bool
192+ isClassNodeIdentifier = isNothing . identType
132193
133194isClassMethodWarning :: T. Text -> Bool
134195isClassMethodWarning = T. isPrefixOf " • No explicit implementation for"
135196
136197minDefToMethodGroups :: BooleanFormula Name -> [[T. Text ]]
137198minDefToMethodGroups = go
138199 where
139- go (Var mn) = [[T. pack ( occNameString ( occName mn)) ]]
200+ go (Var mn) = [[T. pack . occNameString . occName $ mn ]]
140201 go (Or ms) = concatMap (go . unLoc) ms
141202 go (And ms) = foldr (liftA2 (<>) ) [[] ] (fmap (go . unLoc) ms)
142203 go (Parens m) = go (unLoc m)
0 commit comments