|
3 | 3 | module GhcModPluginSpec where
|
4 | 4 |
|
5 | 5 | import Control.Exception
|
| 6 | +import qualified Data.HashMap.Strict as H |
6 | 7 | import qualified Data.Map as Map
|
7 | 8 | #if __GLASGOW_HASKELL__ < 804
|
8 | 9 | import Data.Monoid
|
9 | 10 | #endif
|
10 | 11 | import qualified Data.Set as S
|
11 | 12 | import qualified Data.Text as T
|
12 | 13 | import Haskell.Ide.Engine.MonadTypes
|
| 14 | +import Haskell.Ide.Engine.Plugin.GhcMod |
| 15 | +import Haskell.Ide.Engine.Plugin.HieExtras |
13 | 16 | import Haskell.Ide.Engine.PluginDescriptor
|
14 | 17 | import Haskell.Ide.Engine.PluginUtils
|
15 |
| -import Haskell.Ide.Engine.Plugin.GhcMod |
| 18 | +import Language.Haskell.LSP.Types (TextEdit (..)) |
16 | 19 | import System.Directory
|
17 | 20 | import TestUtils
|
18 | 21 |
|
@@ -112,3 +115,38 @@ ghcmodSpec =
|
112 | 115 | ,(Range (toPos (5,1)) (toPos (5,14)), "Int -> Int")
|
113 | 116 | ]
|
114 | 117 | 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 |
0 commit comments