|
4 | 4 | {-# LANGUAGE ScopedTypeVariables #-}
|
5 | 5 | {-# LANGUAGE TypeOperators #-}
|
6 | 6 | {-# LANGUAGE ViewPatterns #-}
|
| 7 | +{-# LANGUAGE RecordWildCards #-} |
7 | 8 |
|
8 | 9 | module Utils where
|
9 | 10 |
|
@@ -96,39 +97,45 @@ mkTest name fp line col ts = it name $ do
|
96 | 97 | liftIO $
|
97 | 98 | (title `elem` titles) `shouldSatisfy` f
|
98 | 99 |
|
| 100 | +data InvokeTactic = InvokeTactic |
| 101 | + { it_command :: TacticCommand |
| 102 | + , it_argument :: Text |
| 103 | + , it_line :: Int |
| 104 | + , it_col :: Int |
| 105 | + } |
| 106 | + |
| 107 | +invokeTactic :: TextDocumentIdentifier -> InvokeTactic -> Session () |
| 108 | +invokeTactic doc InvokeTactic{..} = do |
| 109 | + -- wait for the entire build to finish, so that Tactics code actions that |
| 110 | + -- use stale data will get uptodate stuff |
| 111 | + void waitForDiagnostics |
| 112 | + void $ waitForTypecheck doc |
| 113 | + actions <- getCodeActions doc $ pointRange it_line it_col |
| 114 | + case find ((== Just (tacticTitle it_command it_argument)) . codeActionTitle) actions of |
| 115 | + Just (InR CodeAction {_command = Just c}) -> do |
| 116 | + executeCommand c |
| 117 | + void $ skipManyTill anyMessage $ message SWorkspaceApplyEdit |
| 118 | + _ -> error $ show actions |
99 | 119 |
|
100 | 120 |
|
101 | 121 | mkGoldenTest
|
102 | 122 | :: (Text -> Text -> Assertion)
|
103 |
| - -> TacticCommand |
104 |
| - -> Text |
105 |
| - -> Int |
106 |
| - -> Int |
| 123 | + -> [InvokeTactic] |
107 | 124 | -> FilePath
|
108 | 125 | -> SpecWith ()
|
109 |
| -mkGoldenTest eq tc occ line col input = |
| 126 | +mkGoldenTest eq invocations input = |
110 | 127 | it (input <> " (golden)") $ do
|
111 | 128 | resetGlobalHoleRef
|
112 | 129 | runSessionForTactics $ do
|
113 | 130 | doc <- openDoc (input <.> "hs") "haskell"
|
114 |
| - -- wait for diagnostics to start coming |
115 |
| - void waitForDiagnostics |
116 |
| - -- wait for the entire build to finish, so that Tactics code actions that |
117 |
| - -- use stale data will get uptodate stuff |
118 |
| - void $ waitForTypecheck doc |
119 |
| - actions <- getCodeActions doc $ pointRange line col |
120 |
| - case find ((== Just (tacticTitle tc occ)) . codeActionTitle) actions of |
121 |
| - Just (InR CodeAction {_command = Just c}) -> do |
122 |
| - executeCommand c |
123 |
| - _resp <- skipManyTill anyMessage (message SWorkspaceApplyEdit) |
124 |
| - edited <- documentContents doc |
125 |
| - let expected_name = input <.> "expected" <.> "hs" |
126 |
| - -- Write golden tests if they don't already exist |
127 |
| - liftIO $ (doesFileExist expected_name >>=) $ flip unless $ do |
128 |
| - T.writeFile expected_name edited |
129 |
| - expected <- liftIO $ T.readFile expected_name |
130 |
| - liftIO $ edited `eq` expected |
131 |
| - _ -> error $ show actions |
| 131 | + traverse_ (invokeTactic doc) invocations |
| 132 | + edited <- documentContents doc |
| 133 | + let expected_name = input <.> "expected" <.> "hs" |
| 134 | + -- Write golden tests if they don't already exist |
| 135 | + liftIO $ (doesFileExist expected_name >>=) $ flip unless $ do |
| 136 | + T.writeFile expected_name edited |
| 137 | + expected <- liftIO $ T.readFile expected_name |
| 138 | + liftIO $ edited `eq` expected |
132 | 139 |
|
133 | 140 | mkCodeLensTest
|
134 | 141 | :: FilePath
|
@@ -197,10 +204,13 @@ mkShowMessageTest tc occ line col input ufm =
|
197 | 204 |
|
198 | 205 |
|
199 | 206 | goldenTest :: TacticCommand -> Text -> Int -> Int -> FilePath -> SpecWith ()
|
200 |
| -goldenTest = mkGoldenTest shouldBe |
| 207 | +goldenTest tc occ line col = mkGoldenTest shouldBe [InvokeTactic tc occ line col] |
| 208 | + |
| 209 | +goldenTestMany :: FilePath -> [InvokeTactic] -> SpecWith () |
| 210 | +goldenTestMany = flip $ mkGoldenTest shouldBe |
201 | 211 |
|
202 | 212 | goldenTestNoWhitespace :: TacticCommand -> Text -> Int -> Int -> FilePath -> SpecWith ()
|
203 |
| -goldenTestNoWhitespace = mkGoldenTest shouldBeIgnoringSpaces |
| 213 | +goldenTestNoWhitespace tc occ line col = mkGoldenTest shouldBeIgnoringSpaces [InvokeTactic tc occ line col] |
204 | 214 |
|
205 | 215 |
|
206 | 216 | shouldBeIgnoringSpaces :: Text -> Text -> Assertion
|
|
0 commit comments