Skip to content

Commit 0fb4728

Browse files
committed
Make casesplit a HaRe action
1 parent adc9958 commit 0fb4728

File tree

4 files changed

+121
-111
lines changed

4 files changed

+121
-111
lines changed

src/Haskell/Ide/Engine/Plugin/GhcMod.hs

Lines changed: 0 additions & 65 deletions
Original file line numberDiff line numberDiff line change
@@ -9,8 +9,6 @@ module Haskell.Ide.Engine.Plugin.GhcMod where
99
import Bag
1010
import Control.Monad.IO.Class
1111
import Control.Lens hiding (cons, children)
12-
import Control.Lens.Setter ((%~))
13-
import Control.Lens.Traversal (traverseOf)
1412
import Data.Aeson
1513
import Data.Function
1614
import qualified Data.HashMap.Strict as HM
@@ -21,7 +19,6 @@ import Data.Maybe
2119
import Data.Monoid ((<>))
2220
import qualified Data.Set as Set
2321
import qualified Data.Text as T
24-
import qualified Data.Text.IO as T
2522
import ErrUtils
2623
import qualified Exception as G
2724
import Name
@@ -35,11 +32,9 @@ import qualified GhcMod.Monad as GM
3532
import qualified GhcMod.SrcUtils as GM
3633
import qualified GhcMod.Types as GM
3734
import qualified GhcMod.Utils as GM
38-
import qualified GhcMod.Exe.CaseSplit as GM
3935
import Haskell.Ide.Engine.MonadFunctions
4036
import Haskell.Ide.Engine.MonadTypes
4137
import Haskell.Ide.Engine.PluginUtils
42-
import Haskell.Ide.Engine.Plugin.HaRe (HarePoint(..))
4338
import qualified Haskell.Ide.Engine.Plugin.HieExtras as Hie
4439
import Haskell.Ide.Engine.ArtifactMap
4540
import qualified Language.Haskell.LSP.Types as LSP
@@ -68,7 +63,6 @@ ghcmodDescriptor plId = PluginDescriptor
6863
, PluginCommand "lint" "Check files using `hlint'" lintCmd
6964
, PluginCommand "info" "Look up an identifier in the context of FILE (like ghci's `:info')" infoCmd
7065
, PluginCommand "type" "Get the type of the expression under (LINE,COL)" typeCmd
71-
, PluginCommand "casesplit" "Generate a pattern match for a binding under (LINE,COL)" splitCaseCmd
7266
]
7367
, pluginCodeActionProvider = Just codeActionProvider
7468
, pluginDiagnosticProvider = Nothing
@@ -307,65 +301,6 @@ cmp a b
307301
isSubRangeOf :: Range -> Range -> Bool
308302
isSubRangeOf (Range sa ea) (Range sb eb) = sb <= sa && eb >= ea
309303

310-
311-
splitCaseCmd :: CommandFunc HarePoint WorkspaceEdit
312-
splitCaseCmd = CmdSync $ \_ (HP uri pos) -> splitCaseCmd' uri pos
313-
314-
splitCaseCmd' :: Uri -> Position -> IdeGhcM (IdeResult WorkspaceEdit)
315-
splitCaseCmd' uri newPos =
316-
pluginGetFile "splitCaseCmd: " uri $ \path -> do
317-
origText <- GM.withMappedFile path $ liftIO . T.readFile
318-
ifCachedModule path (IdeResultOk mempty) $ \tm info -> runGhcModCommand $
319-
case newPosToOld info newPos of
320-
Just oldPos -> do
321-
let (line, column) = unPos oldPos
322-
splitResult' <- GM.splits' path tm line column
323-
case splitResult' of
324-
Just splitResult -> do
325-
wEdit <- liftToGhc $ splitResultToWorkspaceEdit origText splitResult
326-
return $ oldToNewPositions info wEdit
327-
Nothing -> return mempty
328-
Nothing -> return mempty
329-
where
330-
331-
-- | Transform all ranges in a WorkspaceEdit from old to new positions.
332-
oldToNewPositions :: CachedInfo -> WorkspaceEdit -> WorkspaceEdit
333-
oldToNewPositions info wsEdit =
334-
wsEdit
335-
& LSP.documentChanges %~ (>>= traverseOf (traverse . LSP.edits . traverse . LSP.range) (oldRangeToNew info))
336-
& LSP.changes %~ (>>= traverseOf (traverse . traverse . LSP.range) (oldRangeToNew info))
337-
338-
-- | Given the range and text to replace, construct a 'WorkspaceEdit'
339-
-- by diffing the change against the current text.
340-
splitResultToWorkspaceEdit :: T.Text -> GM.SplitResult -> IdeM WorkspaceEdit
341-
splitResultToWorkspaceEdit originalText (GM.SplitResult replaceFromLine replaceFromCol replaceToLine replaceToCol replaceWith) =
342-
diffText (uri, originalText) newText IncludeDeletions
343-
where
344-
before = takeUntil (toPos (replaceFromLine, replaceFromCol)) originalText
345-
after = dropUntil (toPos (replaceToLine, replaceToCol)) originalText
346-
newText = before <> replaceWith <> after
347-
348-
-- | Take the first part of text until the given position.
349-
-- Returns all characters before the position.
350-
takeUntil :: Position -> T.Text -> T.Text
351-
takeUntil (Position l c) txt =
352-
T.unlines takeLines <> takeCharacters
353-
where
354-
textLines = T.lines txt
355-
takeLines = take l textLines
356-
takeCharacters = T.take c (textLines !! c)
357-
358-
-- | Drop the first part of text until the given position.
359-
-- Returns all characters after and including the position.
360-
dropUntil :: Position -> T.Text -> T.Text
361-
dropUntil (Position l c) txt = dropCharacters
362-
where
363-
textLines = T.lines txt
364-
dropLines = drop l textLines
365-
dropCharacters = T.drop c (T.unlines dropLines)
366-
367-
-- ---------------------------------------------------------------------
368-
369304
runGhcModCommand :: IdeGhcM a
370305
-> IdeGhcM (IdeResult a)
371306
runGhcModCommand cmd =

src/Haskell/Ide/Engine/Plugin/HaRe.hs

Lines changed: 85 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,8 @@
77
module Haskell.Ide.Engine.Plugin.HaRe where
88

99
import Control.Lens.Operators
10+
import Control.Lens.Setter ((%~))
11+
import Control.Lens.Traversal (traverseOf)
1012
import Control.Monad.State
1113
import Control.Monad.Trans.Control
1214
import Data.Aeson
@@ -22,12 +24,14 @@ import qualified Data.Text.IO as T
2224
import Exception
2325
import GHC.Generics (Generic)
2426
import qualified GhcMod.Error as GM
27+
import qualified GhcMod.Exe.CaseSplit as GM
2528
import qualified GhcMod.Monad as GM
2629
import qualified GhcMod.Utils as GM
2730
import Haskell.Ide.Engine.ArtifactMap
2831
import Haskell.Ide.Engine.MonadFunctions
2932
import Haskell.Ide.Engine.MonadTypes
3033
import Haskell.Ide.Engine.PluginUtils
34+
import Haskell.Ide.Engine.Plugin.GhcMod (runGhcModCommand)
3135
import qualified Haskell.Ide.Engine.Plugin.HieExtras as Hie
3236
import Language.Haskell.GHC.ExactPrint.Print
3337
import qualified Language.Haskell.LSP.Core as Core
@@ -64,6 +68,9 @@ hareDescriptor plId = PluginDescriptor
6468
deleteDefCmd
6569
, PluginCommand "genapplicative" "Generalise a monadic function to use applicative"
6670
genApplicativeCommand
71+
72+
, PluginCommand "casesplit" "Generate a pattern match for a binding under (LINE,COL)"
73+
splitCaseCmd
6774
]
6875
, pluginCodeActionProvider = Just codeActionProvider
6976
, pluginDiagnosticProvider = Nothing
@@ -213,6 +220,64 @@ genApplicativeCommand' uri pos =
213220

214221
-- ---------------------------------------------------------------------
215222

223+
splitCaseCmd :: CommandFunc HarePoint WorkspaceEdit
224+
splitCaseCmd = CmdSync $ \_ (HP uri pos) -> splitCaseCmd' uri pos
225+
226+
splitCaseCmd' :: Uri -> Position -> IdeGhcM (IdeResult WorkspaceEdit)
227+
splitCaseCmd' uri newPos =
228+
pluginGetFile "splitCaseCmd: " uri $ \path -> do
229+
origText <- GM.withMappedFile path $ liftIO . T.readFile
230+
ifCachedModule path (IdeResultOk mempty) $ \tm info -> runGhcModCommand $
231+
case newPosToOld info newPos of
232+
Just oldPos -> do
233+
let (line, column) = unPos oldPos
234+
splitResult' <- GM.splits' path tm line column
235+
case splitResult' of
236+
Just splitResult -> do
237+
wEdit <- liftToGhc $ splitResultToWorkspaceEdit origText splitResult
238+
return $ oldToNewPositions info wEdit
239+
Nothing -> return mempty
240+
Nothing -> return mempty
241+
where
242+
243+
-- | Transform all ranges in a WorkspaceEdit from old to new positions.
244+
oldToNewPositions :: CachedInfo -> WorkspaceEdit -> WorkspaceEdit
245+
oldToNewPositions info wsEdit =
246+
wsEdit
247+
& J.documentChanges %~ (>>= traverseOf (traverse . J.edits . traverse . J.range) (oldRangeToNew info))
248+
& J.changes %~ (>>= traverseOf (traverse . traverse . J.range) (oldRangeToNew info))
249+
250+
-- | Given the range and text to replace, construct a 'WorkspaceEdit'
251+
-- by diffing the change against the current text.
252+
splitResultToWorkspaceEdit :: T.Text -> GM.SplitResult -> IdeM WorkspaceEdit
253+
splitResultToWorkspaceEdit originalText (GM.SplitResult replaceFromLine replaceFromCol replaceToLine replaceToCol replaceWith) =
254+
diffText (uri, originalText) newText IncludeDeletions
255+
where
256+
before = takeUntil (toPos (replaceFromLine, replaceFromCol)) originalText
257+
after = dropUntil (toPos (replaceToLine, replaceToCol)) originalText
258+
newText = before <> replaceWith <> after
259+
260+
-- | Take the first part of text until the given position.
261+
-- Returns all characters before the position.
262+
takeUntil :: Position -> T.Text -> T.Text
263+
takeUntil (Position l c) txt =
264+
T.unlines takeLines <> takeCharacters
265+
where
266+
textLines = T.lines txt
267+
takeLines = take l textLines
268+
takeCharacters = T.take c (textLines !! c)
269+
270+
-- | Drop the first part of text until the given position.
271+
-- Returns all characters after and including the position.
272+
dropUntil :: Position -> T.Text -> T.Text
273+
dropUntil (Position l c) txt = dropCharacters
274+
where
275+
textLines = T.lines txt
276+
dropLines = drop l textLines
277+
dropCharacters = T.drop c (T.unlines dropLines)
278+
279+
-- ---------------------------------------------------------------------
280+
216281
getRefactorResult :: [ApplyRefacResult] -> [(FilePath,T.Text)]
217282
getRefactorResult = map getNewFile . filter fileModified
218283
where fileModified ((_,m),_) = m == RefacModified
@@ -294,20 +359,26 @@ hoist f a =
294359
codeActionProvider :: CodeActionProvider
295360
codeActionProvider pId docId _ _ (J.Range pos _) _ =
296361
pluginGetFile "HaRe codeActionProvider: " (docId ^. J.uri) $ \file ->
297-
ifCachedInfo file (IdeResultOk mempty) $ \info -> do
298-
let symbols = getArtifactsAtPos pos (defMap info)
299-
debugm $ show $ map (Hie.showName . snd) symbols
300-
if not (null symbols)
301-
then
302-
let name = Hie.showName $ snd $ head symbols
303-
in IdeResultOk <$> sequence [
362+
ifCachedInfo file (IdeResultOk mempty) $ \info ->
363+
case getArtifactsAtPos pos (defMap info) of
364+
[h] -> do
365+
let name = Hie.showName $ snd h
366+
debugm $ show name
367+
IdeResultOk <$> sequence [
304368
mkLiftOneAction name
305369
, mkLiftTopAction name
306370
, mkDemoteAction name
307371
, mkDeleteAction name
308372
, mkDuplicateAction name
309373
]
310-
else return (IdeResultOk [])
374+
_ -> case getArtifactsAtPos pos (locMap info) of
375+
[h] -> do
376+
let name = Hie.showName $ snd h
377+
debugm $ show name
378+
IdeResultOk <$> sequence [
379+
mkCaseSplitAction name
380+
]
381+
_ -> return $ IdeResultOk []
311382

312383
where
313384
mkLiftOneAction name = do
@@ -339,3 +410,9 @@ codeActionProvider pId docId _ _ (J.Range pos _) _ =
339410
title = "Duplicate definition of " <> name
340411
dupCmd <- mkLspCommand pId "dupdef" title (Just args)
341412
return $ J.CodeAction title (Just J.CodeActionRefactor) mempty Nothing (Just dupCmd)
413+
414+
mkCaseSplitAction name = do
415+
let args = [J.toJSON $ HP (docId ^. J.uri) pos]
416+
title = "Case split on " <> name
417+
splCmd <- mkLspCommand pId "casesplit" title (Just args)
418+
return $ J.CodeAction title (Just J.CodeActionRefactorRewrite) mempty Nothing (Just splCmd)

test/unit/GhcModPluginSpec.hs

Lines changed: 0 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,6 @@
33
module GhcModPluginSpec where
44

55
import Control.Exception
6-
import qualified Data.HashMap.Strict as H
76
import qualified Data.Map as Map
87
#if __GLASGOW_HASKELL__ < 804
98
import Data.Monoid
@@ -14,8 +13,6 @@ import Haskell.Ide.Engine.MonadTypes
1413
import Haskell.Ide.Engine.PluginDescriptor
1514
import Haskell.Ide.Engine.PluginUtils
1615
import Haskell.Ide.Engine.Plugin.GhcMod
17-
import Haskell.Ide.Engine.Plugin.HaRe ( HarePoint(..) )
18-
import Language.Haskell.LSP.Types ( TextEdit(..) )
1916
import System.Directory
2017
import TestUtils
2118

@@ -115,38 +112,3 @@ ghcmodSpec =
115112
,(Range (toPos (5,1)) (toPos (5,14)), "Int -> Int")
116113
]
117114
testCommand testPlugins act "ghcmod" "type"dummyVfs arg res
118-
119-
-- ---------------------------------
120-
121-
it "runs the casesplit command" $ cdAndDo "./test/testdata" $ do
122-
fp <- makeAbsolute "GhcModCaseSplit.hs"
123-
let uri = filePathToUri fp
124-
act = do
125-
_ <- setTypecheckedModule uri
126-
splitCaseCmd' uri (toPos (5,5))
127-
arg = HP uri (toPos (5,5))
128-
res = IdeResultOk $ WorkspaceEdit
129-
(Just $ H.singleton uri
130-
$ List [TextEdit (Range (Position 4 0) (Position 4 10))
131-
"foo Nothing = ()\nfoo (Just x) = ()"])
132-
Nothing
133-
testCommand testPlugins act "ghcmod" "casesplit" dummyVfs arg res
134-
135-
it "runs the casesplit command with an absolute path from another folder, correct params" $ do
136-
fp <- makeAbsolute "./test/testdata/GhcModCaseSplit.hs"
137-
cd <- getCurrentDirectory
138-
cd2 <- getHomeDirectory
139-
bracket (setCurrentDirectory cd2)
140-
(\_-> setCurrentDirectory cd)
141-
$ \_-> do
142-
let uri = filePathToUri fp
143-
act = do
144-
_ <- setTypecheckedModule uri
145-
splitCaseCmd' uri (toPos (5,5))
146-
arg = HP uri (toPos (5,5))
147-
res = IdeResultOk $ WorkspaceEdit
148-
(Just $ H.singleton uri
149-
$ List [TextEdit (Range (Position 4 0) (Position 4 10))
150-
"foo Nothing = ()\nfoo (Just x) = ()"])
151-
Nothing
152-
testCommand testPlugins act "ghcmod" "casesplit" dummyVfs arg res

test/unit/HaRePluginSpec.hs

Lines changed: 36 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
66
module HaRePluginSpec where
77

8+
import Control.Exception
89
import Control.Monad.Trans.Free
910
import Control.Monad.IO.Class
1011
import Data.Aeson
@@ -173,6 +174,41 @@ hareSpec = do
173174

174175
-- ---------------------------------
175176

177+
it "runs the casesplit command" $ cdAndDo "./test/testdata" $ do
178+
fp <- makeAbsolute "GhcModCaseSplit.hs"
179+
let uri = filePathToUri fp
180+
act = do
181+
_ <- setTypecheckedModule uri
182+
splitCaseCmd' uri (toPos (5,5))
183+
arg = HP uri (toPos (5,5))
184+
res = IdeResultOk $ WorkspaceEdit
185+
(Just $ H.singleton uri
186+
$ List [TextEdit (Range (Position 4 0) (Position 4 10))
187+
"foo Nothing = ()\nfoo (Just x) = ()"])
188+
Nothing
189+
testCommand testPlugins act "hare" "casesplit" dummyVfs arg res
190+
191+
it "runs the casesplit command with an absolute path from another folder, correct params" $ do
192+
fp <- makeAbsolute "./test/testdata/GhcModCaseSplit.hs"
193+
cd <- getCurrentDirectory
194+
cd2 <- getHomeDirectory
195+
bracket (setCurrentDirectory cd2)
196+
(\_-> setCurrentDirectory cd)
197+
$ \_-> do
198+
let uri = filePathToUri fp
199+
act = do
200+
_ <- setTypecheckedModule uri
201+
splitCaseCmd' uri (toPos (5,5))
202+
arg = HP uri (toPos (5,5))
203+
res = IdeResultOk $ WorkspaceEdit
204+
(Just $ H.singleton uri
205+
$ List [TextEdit (Range (Position 4 0) (Position 4 10))
206+
"foo Nothing = ()\nfoo (Just x) = ()"])
207+
Nothing
208+
testCommand testPlugins act "hare" "casesplit" dummyVfs arg res
209+
210+
-- ---------------------------------
211+
176212
describe "Additional GHC API commands" $ do
177213
cwd <- runIO getCurrentDirectory
178214

0 commit comments

Comments
 (0)