@@ -32,11 +32,15 @@ tests = testGroup "Language.Haskell.Stylish.Step.Imports.Tests"
3232 , testCase " case 06" case06
3333 , testCase " case 07" case07
3434 , testCase " case 08" case08
35+ , testCase " case 08b" case08b
3536 , testCase " case 09" case09
3637 , testCase " case 10" case10
3738 , testCase " case 11" case11
39+ , testCase " case 11b" case11b
3840 , testCase " case 12" case12
41+ , testCase " case 12b" case12b
3942 , testCase " case 13" case13
43+ , testCase " case 13b" case13b
4044 , testCase " case 14" case14
4145 , testCase " case 15" case15
4246 , testCase " case 16" case16
@@ -50,6 +54,7 @@ tests = testGroup "Language.Haskell.Stylish.Step.Imports.Tests"
5054 , testCase " case 21" case21
5155 , testCase " case 22" case22
5256 , testCase " case 23" case23
57+ , testCase " case 23b" case23b
5358 , testCase " case 24" case24
5459 , testCase " case 25" case25
5560 , testCase " case 26 (issue 185)" case26
@@ -212,6 +217,28 @@ case08 = expected
212217 ]
213218
214219
220+ --------------------------------------------------------------------------------
221+ case08b :: Assertion
222+ case08b = expected
223+ @=? testStep (step 80 $ Options Global WithModuleName True Inline Inherit (LPConstant 4 ) True False ) input
224+ where
225+ expected = unlines
226+ [" module Herp where"
227+ , " "
228+ , " import Control.Monad"
229+ , " import Data.List as List (concat, foldl, foldr, head, init,"
230+ , " last, length, map, null, reverse, tail, (++))"
231+ , " import Data.Map (Map, insert, lookup, (!))"
232+ , " import qualified Data.Map as M"
233+ , " import Only.Instances ()"
234+ , " "
235+ , " import Foo (Bar (..))"
236+ , " import Herp.Derp.Internals hiding (foo)"
237+ , " "
238+ , " herp = putStrLn \" import Hello world\" "
239+ ]
240+
241+
215242--------------------------------------------------------------------------------
216243case09 :: Assertion
217244case09 = expected
@@ -313,6 +340,27 @@ case11 = expected
313340 ]
314341
315342
343+ case11b :: Assertion
344+ case11b = expected
345+ @=? testStep (step 80 $ Options Group WithModuleName True Inline Inherit (LPConstant 4 ) True False ) input
346+ where
347+ expected = unlines
348+ [ " module Herp where"
349+ , " "
350+ , " import Control.Monad"
351+ , " import Data.List as List (concat, foldl, foldr, head, init, last,"
352+ , " length, map, null, reverse, tail, (++))"
353+ , " import Data.Map (Map, insert, lookup, (!))"
354+ , " import qualified Data.Map as M"
355+ , " import Only.Instances ()"
356+ , " "
357+ , " import Foo (Bar (..))"
358+ , " import Herp.Derp.Internals hiding (foo)"
359+ , " "
360+ , " herp = putStrLn \" import Hello world\" "
361+ ]
362+
363+
316364--------------------------------------------------------------------------------
317365case12 :: Assertion
318366case12 = expected
@@ -328,6 +376,18 @@ case12 = expected
328376 ]
329377
330378
379+ --------------------------------------------------------------------------------
380+ case12b :: Assertion
381+ case12b = expected
382+ @=? testStep (step 80 $ Options Group WithModuleName True Inline Inherit (LPConstant 2 ) True False ) input'
383+ where
384+ input' = unlines
385+ [ " import Data.List (map)"
386+ ]
387+
388+ expected = input'
389+
390+
331391--------------------------------------------------------------------------------
332392case13 :: Assertion
333393case13 = expected
@@ -345,6 +405,23 @@ case13 = expected
345405 ]
346406
347407
408+ --------------------------------------------------------------------------------
409+ case13b :: Assertion
410+ case13b = expected
411+ @=? testStep (step 80 $ Options None WithModuleName True InlineWithBreak Inherit (LPConstant 4 ) True False ) input'
412+ where
413+ input' = unlines
414+ [ " import qualified Data.List as List (concat, foldl, foldr, head, init,"
415+ , " last, length, map, null, reverse, tail, (++))"
416+ ]
417+
418+ expected = unlines
419+ [ " import qualified Data.List as List"
420+ , " (concat, foldl, foldr, head, init, last, length, map, null, reverse, tail,"
421+ , " (++))"
422+ ]
423+
424+
348425--------------------------------------------------------------------------------
349426case14 :: Assertion
350427case14 = expected
@@ -451,6 +528,7 @@ case18 = expected @=? testStep
451528 , " import Data.Acid as Acid (closeAcidState, createCheckpoint, openLocalStateFrom)"
452529 ]
453530
531+
454532--------------------------------------------------------------------------------
455533case19 :: Assertion
456534case19 = expected @=? testStep
@@ -467,6 +545,7 @@ case19 = expected @=? testStep
467545 , " intersperse)"
468546 ]
469547
548+
470549case19b :: Assertion
471550case19b = expected @=? testStep
472551 (step 40 $ Options File NewLine True InlineWithBreak RightAfter (LPConstant 17 ) True False ) case19input
@@ -482,6 +561,7 @@ case19b = expected @=? testStep
482561 , " intersperse)"
483562 ]
484563
564+
485565case19c :: Assertion
486566case19c = expected @=? testStep
487567 (step 40 $ Options File NewLine True InlineWithBreak RightAfter LPModuleName True False ) case19input
@@ -497,6 +577,7 @@ case19c = expected @=? testStep
497577 , " intersperse)"
498578 ]
499579
580+
500581case19d :: Assertion
501582case19d = expected @=? testStep
502583 (step 40 $ Options Global NewLine True InlineWithBreak RightAfter LPModuleName True False ) case19input
@@ -512,6 +593,7 @@ case19d = expected @=? testStep
512593 , " intersperse)"
513594 ]
514595
596+
515597case19input :: String
516598case19input = unlines
517599 [ " import Prelude.Compat hiding (foldMap)"
@@ -520,6 +602,7 @@ case19input = unlines
520602 , " import Data.List (foldl', intercalate, intersperse)"
521603 ]
522604
605+
523606--------------------------------------------------------------------------------
524607case20 :: Assertion
525608case20 = expected
@@ -538,6 +621,7 @@ case20 = expected
538621 , " import Data.Set (empty)"
539622 ]
540623
624+
541625--------------------------------------------------------------------------------
542626case21 :: Assertion
543627case21 = expected
@@ -568,6 +652,7 @@ case21 = expected
568652 , " import X9 hiding (x, y, z, x)"
569653 ]
570654
655+
571656--------------------------------------------------------------------------------
572657case22 :: Assertion
573658case22 = expected
@@ -594,6 +679,7 @@ case22 = expected
594679 " theLongestNameYet, shortName)"
595680 ]
596681
682+
597683--------------------------------------------------------------------------------
598684case23 :: Assertion
599685case23 = expected
@@ -618,6 +704,33 @@ case23 = expected
618704 , " import Data.ALongName.Foo (Foo, Goo, Boo)"
619705 ]
620706
707+
708+ --------------------------------------------------------------------------------
709+ case23b :: Assertion
710+ case23b = expected
711+ @=? testStep (step 40 $ Options None WithModuleName False Inline Inherit (LPConstant 4 ) True True ) input'
712+ where
713+ expected = unlines
714+ [ " import Data.Acid ( AcidState )"
715+ , " import Data.Default.Class"
716+ , " ( Default (def) )"
717+ , " "
718+ , " import Data.Monoid ( (<>) )"
719+ , " "
720+ , " import Data.ALongName.Foo ( Boo, Foo,"
721+ , " Goo )"
722+ ]
723+
724+ input' = unlines
725+ [ " import Data.Acid (AcidState)"
726+ , " import Data.Default.Class (Default(def))"
727+ , " "
728+ , " import Data.Monoid ((<>) )"
729+ , " "
730+ , " import Data.ALongName.Foo (Foo, Goo, Boo)"
731+ ]
732+
733+
621734--------------------------------------------------------------------------------
622735case24 :: Assertion
623736case24 = expected
@@ -641,6 +754,7 @@ case24 = expected
641754 " GooReallyLong, BooReallyLong)"
642755 ]
643756
757+
644758--------------------------------------------------------------------------------
645759case25 :: Assertion
646760case25 = expected
0 commit comments