@@ -13,16 +13,24 @@ module Ide.Plugin.OverloadedRecordDot
1313
1414-- based off of Berk Okzuturk's hls-explicit-records-fields-plugin
1515
16- import Control.Lens ((^.) )
16+ import Control.Lens (_Just , (^.) , (^?) )
17+ import Control.Monad (replicateM )
1718import Control.Monad.IO.Class (MonadIO , liftIO )
18- import Control.Monad.Trans.Except (ExceptT )
19+ import Control.Monad.Trans.Class (lift )
20+ import Control.Monad.Trans.Except (ExceptT , throwE )
21+ import Data.Aeson (FromJSON , Result (.. ),
22+ ToJSON , fromJSON , toJSON )
1923import Data.Generics (GenericQ , everything ,
2024 everythingBut , mkQ )
25+ import qualified Data.IntMap.Strict as IntMap
2126import qualified Data.Map as Map
22- import Data.Maybe (mapMaybe , maybeToList )
27+ import Data.Maybe (fromJust , mapMaybe ,
28+ maybeToList )
2329import Data.Text (Text )
30+ import Data.Unique (hashUnique , newUnique )
2431import Development.IDE (IdeState ,
2532 NormalizedFilePath ,
33+ NormalizedUri ,
2634 Pretty (.. ), Range ,
2735 Recorder (.. ), Rules ,
2836 WithPriority (.. ),
@@ -75,18 +83,22 @@ import Ide.Types (PluginDescriptor (..),
7583 PluginId (.. ),
7684 PluginMethodHandler ,
7785 defaultPluginDescriptor ,
86+ mkCodeActionHandlerWithResolve ,
7887 mkPluginHandler )
88+ import Language.LSP.Protocol.Lens (HasChanges (changes ))
7989import qualified Language.LSP.Protocol.Lens as L
8090import Language.LSP.Protocol.Message (Method (.. ),
8191 SMethod (.. ))
8292import Language.LSP.Protocol.Types (CodeAction (.. ),
8393 CodeActionKind (CodeActionKind_RefactorRewrite ),
8494 CodeActionParams (.. ),
8595 Command , TextEdit (.. ),
86- WorkspaceEdit (WorkspaceEdit ),
96+ Uri (.. ),
97+ WorkspaceEdit (WorkspaceEdit , _changeAnnotations , _changes , _documentChanges ),
8798 fromNormalizedUri ,
8899 normalizedFilePathToUri ,
89100 type (|? ) (.. ))
101+ import Language.LSP.Server (getClientCapabilities )
90102data Log
91103 = LogShake Shake. Log
92104 | LogCollectedRecordSelectors [RecordSelectorExpr ]
@@ -105,7 +117,14 @@ instance Hashable CollectRecordSelectors
105117instance NFData CollectRecordSelectors
106118
107119data CollectRecordSelectorsResult = CRSR
108- { recordInfos :: RangeMap RecordSelectorExpr
120+ { -- | We store everything in here that we need to create the unresolved
121+ -- codeAction: the range, an uniquely identifiable int, and the selector
122+ -- selector expression (HSExpr) that we use to generate the name
123+ records :: RangeMap (Int , HsExpr (GhcPass 'Renamed))
124+ -- | This is for when we need to fully generate a textEdit. It contains the
125+ -- whole expression we are interested in indexed to the unique id we got
126+ -- from the previous field
127+ , recordInfos :: IntMap. IntMap RecordSelectorExpr
109128 , enabledExtensions :: [Extension ]
110129 }
111130 deriving (Generic )
@@ -135,56 +154,85 @@ instance Pretty RecordSelectorExpr where
135154instance NFData RecordSelectorExpr where
136155 rnf = rwhnf
137156
157+ -- | The data that is serialized and placed in the data field of resolvable
158+ -- code actions
159+ data ORDResolveData = ORDRD {
160+ -- | We need the uri to get shake results
161+ uri :: Uri
162+ -- | The unique id that allows us to find the specific codeAction we want
163+ , uniqueID :: Int
164+ } deriving (Generic , Show )
165+ instance ToJSON ORDResolveData
166+ instance FromJSON ORDResolveData
167+
138168descriptor :: Recorder (WithPriority Log ) -> PluginId
139169 -> PluginDescriptor IdeState
140170descriptor recorder plId = (defaultPluginDescriptor plId)
141171 { pluginHandlers =
142- mkPluginHandler SMethod_TextDocumentCodeAction codeActionProvider
172+ mkCodeActionHandlerWithResolve codeActionProvider resolveProvider
143173 , pluginRules = collectRecSelsRule recorder
144174 }
145175
176+ resolveProvider :: PluginMethodHandler IdeState 'Method_CodeActionResolve
177+ resolveProvider ideState pId ca@ (CodeAction _ _ _ _ _ _ _ (Just resData)) =
178+ pluginResponse $ do
179+ case fromJSON resData of
180+ Success (ORDRD uri int) -> do
181+ nfp <- getNormalizedFilePath uri
182+ CRSR _ crsDetails exts <- collectRecSelResult ideState nfp
183+ pragma <- getFirstPragma pId ideState nfp
184+ case IntMap. lookup int crsDetails of
185+ Just rse -> pure $ ca {_edit = mkWorkspaceEdit uri rse exts pragma}
186+ -- We need to throw a content modified error here, see
187+ -- https://github.com/microsoft/language-server-protocol/issues/1738
188+ -- but we need fendor's plugin error response pr to make it
189+ -- convenient to use here, so we will wait to do that till that's merged
190+ _ -> throwE " Content Modified Error"
191+ _ -> throwE " Unable to deserialize the data"
192+
146193codeActionProvider :: PluginMethodHandler IdeState 'Method_TextDocumentCodeAction
147194codeActionProvider ideState pId (CodeActionParams _ _ caDocId caRange _) =
148195 pluginResponse $ do
149196 nfp <- getNormalizedFilePath (caDocId ^. L. uri)
150- pragma <- getFirstPragma pId ideState nfp
151- CRSR crsMap exts <- collectRecSelResult ideState nfp
152- let pragmaEdit =
153- if OverloadedRecordDot `elem` exts
154- then Nothing
155- else Just $ insertNewPragma pragma OverloadedRecordDot
156- edits crs = convertRecordSelectors crs : maybeToList pragmaEdit
157- changes crs =
158- Just $ Map. singleton (fromNormalizedUri
159- (normalizedFilePathToUri nfp))
160- (edits crs)
161- mkCodeAction crs = InR CodeAction
197+ CRSR crsMap crsDetails exts <- collectRecSelResult ideState nfp
198+ let mkCodeAction (crsM, nse) = InR CodeAction
162199 { -- We pass the record selector to the title function, so that
163200 -- we can have the name of the record selector in the title of
164201 -- the codeAction. This allows the user can easily distinguish
165202 -- between the different codeActions when using nested record
166203 -- selectors, the disadvantage is we need to print out the
167204 -- name of the record selector which will decrease performance
168- _title = mkCodeActionTitle exts crs
205+ _title = mkCodeActionTitle exts crsM nse
169206 , _kind = Just CodeActionKind_RefactorRewrite
170207 , _diagnostics = Nothing
171208 , _isPreferred = Nothing
172209 , _disabled = Nothing
173- , _edit = Just $ WorkspaceEdit (changes crs) Nothing Nothing
210+ , _edit = Nothing
174211 , _command = Nothing
175- , _data_ = Nothing
212+ , _data_ = Just $ toJSON $ ORDRD (caDocId ^. L. uri) crsM
176213 }
177214 actions = map mkCodeAction (RangeMap. filterByRange caRange crsMap)
178215 pure $ InL actions
179216 where
180- mkCodeActionTitle :: [Extension ] -> RecordSelectorExpr -> Text
181- mkCodeActionTitle exts ( RecordSelectorExpr _ se _) =
217+ mkCodeActionTitle :: [Extension ] -> Int -> HsExpr ( GhcPass 'Renamed) -> Text
218+ mkCodeActionTitle exts crsM se =
182219 if OverloadedRecordDot `elem` exts
183220 then title
184221 else title <> " (needs extension: OverloadedRecordDot)"
185222 where
186- title = " Convert `" <> name <> " ` to record dot syntax"
187- name = printOutputable se
223+ title = " Convert `" <> printOutputable se <> " ` to record dot syntax"
224+
225+ mkWorkspaceEdit :: Uri -> RecordSelectorExpr -> [Extension ] -> NextPragmaInfo -> Maybe WorkspaceEdit
226+ mkWorkspaceEdit uri recSel exts pragma =
227+ Just $ WorkspaceEdit
228+ { _changes =
229+ Just (Map. singleton uri (convertRecordSelectors recSel : maybeToList pragmaEdit))
230+ , _documentChanges = Nothing
231+ , _changeAnnotations = Nothing }
232+ where pragmaEdit =
233+ if OverloadedRecordDot `elem` exts
234+ then Nothing
235+ else Just $ insertNewPragma pragma OverloadedRecordDot
188236
189237collectRecSelsRule :: Recorder (WithPriority Log ) -> Rules ()
190238collectRecSelsRule recorder = define (cmapWithPrio LogShake recorder) $
@@ -201,11 +249,17 @@ collectRecSelsRule recorder = define (cmapWithPrio LogShake recorder) $
201249 -- the OverloadedRecordDot pragma
202250 exts = getEnabledExtensions tmr
203251 recSels = mapMaybe (rewriteRange pm) (getRecordSelectors tmr)
252+ -- We are creating a list as long as our rec selectors of unique int s
253+ -- created by calling hashUnique on a Unique. The reason why we are
254+ -- extracting the ints is because they don't need any work to serialize.
255+ uniques <- liftIO $ replicateM (length recSels) (hashUnique <$> newUnique)
204256 logWith recorder Debug (LogCollectedRecordSelectors recSels)
205- let -- We need the rangeMap to be able to filter by range later
206- crsMap :: RangeMap RecordSelectorExpr
207- crsMap = RangeMap. fromList location recSels
208- pure ([] , CRSR <$> Just crsMap <*> Just exts)
257+ let crsUniquesAndDetails = zip uniques recSels
258+ -- We need the rangeMap to be able to filter by range later
259+ rangeAndUnique = toRangeAndUnique <$> crsUniquesAndDetails
260+ crsMap :: RangeMap (Int , HsExpr (GhcPass 'Renamed))
261+ crsMap = RangeMap. fromList' rangeAndUnique
262+ pure ([] , CRSR <$> Just crsMap <*> Just (IntMap. fromList crsUniquesAndDetails) <*> Just exts)
209263 where getEnabledExtensions :: TcModuleResult -> [Extension ]
210264 getEnabledExtensions = getExtensions . tmrParsed
211265 getRecordSelectors :: TcModuleResult -> [RecordSelectorExpr ]
@@ -217,6 +271,7 @@ collectRecSelsRule recorder = define (cmapWithPrio LogShake recorder) $
217271 case toCurrentRange pm (location recSel) of
218272 Just newLoc -> Just $ recSel{location = newLoc}
219273 Nothing -> Nothing
274+ toRangeAndUnique (id , RecordSelectorExpr l (unLoc -> se) _) = (l, (id , se))
220275
221276convertRecordSelectors :: RecordSelectorExpr -> TextEdit
222277convertRecordSelectors (RecordSelectorExpr l se re) =
0 commit comments