Skip to content
This repository was archived by the owner on Oct 7, 2020. It is now read-only.

Commit 55ccdd3

Browse files
committed
Add tests to force overflows for formatters
1 parent 88cc608 commit 55ccdd3

File tree

2 files changed

+65
-10
lines changed

2 files changed

+65
-10
lines changed

test/testdata/CodeActionImportListElaborate.hs

+1
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE NoImplicitPrelude #-}
22
import System.IO (IO)
3+
import Data.List (find, head, last, tail, init, union, (\\), null, length, cons, uncons)
34
-- | Main entry point to the program
45
main :: IO ()
56
main =

test/unit/HsImportSpec.hs

+64-10
Original file line numberDiff line numberDiff line change
@@ -33,12 +33,15 @@ testPlugins = pluginDescToIdePlugins
3333
, Ormolu.ormoluDescriptor "ormolu"
3434
]
3535

36-
brittanyFilePath :: FilePath
37-
brittanyFilePath = "test" </> "testdata" </> "CodeActionImportList.hs"
36+
codeActionImportList :: FilePath
37+
codeActionImportList = "test" </> "testdata" </> "CodeActionImportList.hs"
38+
39+
codeActionBigImportList :: FilePath
40+
codeActionBigImportList = "test" </> "testdata" </> "CodeActionImportListElaborate.hs"
3841

3942
dispatchRequestP :: IdeGhcM a -> IO a
4043
dispatchRequestP act = do
41-
cwd <- liftIO $ getCurrentDirectory
44+
cwd <- liftIO getCurrentDirectory
4245
runIGM testPlugins (cwd </> "test" </> "testdata" </> "File.hs") act
4346

4447
-- ---------------------------------------------------------------------
@@ -59,6 +62,26 @@ hsImportSpec = do
5962
]
6063
, [ TextEdit (Range (toPos (2, 1)) (toPos (2, 1))) "import Data.Function ( ($) )\n"
6164
]
65+
, [ TextEdit (Range (toPos (2, 1)) (toPos (2, 32))) $
66+
"import System.IO ( IO\n" <>
67+
" , hPutStrLn\n" <>
68+
" )"
69+
]
70+
, [ TextEdit (Range (toPos (3, 1)) (toPos (3, 99))) $
71+
"import Data.List ( find\n" <>
72+
" , head\n" <>
73+
" , last\n" <>
74+
" , tail\n" <>
75+
" , init\n" <>
76+
" , union\n" <>
77+
" , (\\\\)\n" <>
78+
" , null\n" <>
79+
" , length\n" <>
80+
" , cons\n" <>
81+
" , uncons\n" <>
82+
" , reverse\n" <>
83+
" )"
84+
]
6285
]
6386
describe "formats with floskell" $ hsImportSpecRunner "floskell"
6487
[ -- Expected output for simple format.
@@ -74,6 +97,12 @@ hsImportSpec = do
7497
]
7598
, [ TextEdit (Range (toPos (2, 1)) (toPos (2, 1))) "import Data.Function (($))\n"
7699
]
100+
, [ TextEdit (Range (toPos (2, 1)) (toPos (2, 32))) "import System.IO (IO, hPutStrLn)"
101+
]
102+
, [ TextEdit (Range (toPos (3, 1)) (toPos (3, 99))) $
103+
"import Data.List (find, head, last, tail, init, union, (\\\\), null\n" <>
104+
" , length, cons, uncons, reverse)"
105+
]
77106
]
78107
describe "formats with ormolu" $ case ghcVersion of
79108
GHC86 -> hsImportSpecRunner "ormolu"
@@ -90,6 +119,10 @@ hsImportSpec = do
90119
]
91120
, [ TextEdit (Range (toPos (2, 1)) (toPos (2, 1))) "import Data.Function (($))\n"
92121
]
122+
, [ TextEdit (Range (toPos (2, 1)) (toPos (2, 32))) "import System.IO (IO, hPutStrLn)"
123+
]
124+
, [ TextEdit (Range (toPos (3, 1)) (toPos (3, 99))) "import Data.List ((\\\\), cons, find, head, init, last, length, null, reverse, tail, uncons, union)"
125+
]
93126
]
94127
_ -> it "is NOP formatter" $
95128
pendingWith "Ormolu only supported by GHC >= 8.6. Need to restore this."
@@ -98,9 +131,9 @@ hsImportSpec = do
98131
-- Parameterized HsImport Spec.
99132
-- ---------------------------------------------------------------------
100133
hsImportSpecRunner :: T.Text -> [[TextEdit]] -> Spec
101-
hsImportSpecRunner formatterName [e1, e2, e3, e4, e5, e6] = do
134+
hsImportSpecRunner formatterName [e1, e2, e3, e4, e5, e6, e7, e8] = do
102135
it "formats" $ do
103-
fp <- makeAbsolute brittanyFilePath
136+
fp <- makeAbsolute codeActionImportList
104137
let uri = filePathToUri fp
105138
let act = importModule (ImportParams uri Simple "Control.Monad")
106139

@@ -110,7 +143,7 @@ hsImportSpecRunner formatterName [e1, e2, e3, e4, e5, e6] = do
110143
Nothing -> fail "No Change found"
111144

112145
it "import-list formats" $ do
113-
fp <- makeAbsolute brittanyFilePath
146+
fp <- makeAbsolute codeActionImportList
114147
let uri = filePathToUri fp
115148
let act = importModule (ImportParams uri (Complex (Import $ Only "when")) "Control.Monad")
116149

@@ -120,7 +153,7 @@ hsImportSpecRunner formatterName [e1, e2, e3, e4, e5, e6] = do
120153
Nothing -> fail "No Change found"
121154

122155
it "import-list type formats" $ do
123-
fp <- makeAbsolute brittanyFilePath
156+
fp <- makeAbsolute codeActionImportList
124157
let uri = filePathToUri fp
125158
let act = importModule (ImportParams uri (Complex (Import $ Only "Maybe")) "Data.Maybe")
126159

@@ -130,7 +163,7 @@ hsImportSpecRunner formatterName [e1, e2, e3, e4, e5, e6] = do
130163
Nothing -> fail "No Change found"
131164

132165
it "import-list constructor formats" $ do
133-
fp <- makeAbsolute brittanyFilePath
166+
fp <- makeAbsolute codeActionImportList
134167
let uri = filePathToUri fp
135168
let act = importModule (ImportParams uri (Complex (Import $ AllOf "Maybe")) "Data.Maybe")
136169

@@ -140,7 +173,7 @@ hsImportSpecRunner formatterName [e1, e2, e3, e4, e5, e6] = do
140173
Nothing -> fail "No Change found"
141174

142175
it "import-list constructor formats" $ do
143-
fp <- makeAbsolute brittanyFilePath
176+
fp <- makeAbsolute codeActionImportList
144177
let uri = filePathToUri fp
145178
let act = importModule (ImportParams uri (Complex (Import $ OneOf "Maybe" "Nothing")) "Data.Maybe")
146179

@@ -150,7 +183,7 @@ hsImportSpecRunner formatterName [e1, e2, e3, e4, e5, e6] = do
150183
Nothing -> fail "No Change found"
151184

152185
it "import-list infix function formats" $ do
153-
fp <- makeAbsolute brittanyFilePath
186+
fp <- makeAbsolute codeActionImportList
154187
let uri = filePathToUri fp
155188
let act = importModule (ImportParams uri (Complex (Import $ Only "$")) "Data.Function")
156189

@@ -159,6 +192,27 @@ hsImportSpecRunner formatterName [e1, e2, e3, e4, e5, e6] = do
159192
Just (List val) -> val `shouldBe` e6
160193
Nothing -> fail "No Change found"
161194

195+
it "import-list with existing entry formats" $ do
196+
fp <- makeAbsolute codeActionBigImportList
197+
let uri = filePathToUri fp
198+
let act = importModule (ImportParams uri (Complex (Import $ Only "hPutStrLn")) "System.IO")
199+
200+
IdeResultOk (WorkspaceEdit (Just changes) _) <- runSingle' (setFormatter formatterName) testPlugins fp act
201+
case Map.lookup uri changes of
202+
Just (List val) -> val `shouldBe` e7
203+
Nothing -> fail "No Change found"
204+
205+
it "import-list with forced overflow formats" $ do
206+
fp <- makeAbsolute codeActionBigImportList
207+
let uri = filePathToUri fp
208+
let act = importModule (ImportParams uri (Complex (Import $ Only "reverse")) "Data.List")
209+
210+
IdeResultOk (WorkspaceEdit (Just changes) _) <- runSingle' (setFormatter formatterName) testPlugins fp act
211+
case Map.lookup uri changes of
212+
Just (List val) -> val `shouldBe` e8
213+
Nothing -> fail "No Change found"
214+
215+
162216
-- Silence warnings
163217
hsImportSpecRunner formatter args =
164218
error $ "Not the right amount of arguments for \"hsImportSpec ("

0 commit comments

Comments
 (0)