summaryrefslogtreecommitdiffhomepage
path: root/tests/Language/Haskell/Stylish/Step/Imports/Tests.hs
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Language/Haskell/Stylish/Step/Imports/Tests.hs')
-rw-r--r--tests/Language/Haskell/Stylish/Step/Imports/Tests.hs162
1 files changed, 147 insertions, 15 deletions
diff --git a/tests/Language/Haskell/Stylish/Step/Imports/Tests.hs b/tests/Language/Haskell/Stylish/Step/Imports/Tests.hs
index c3178ac..bc6772c 100644
--- a/tests/Language/Haskell/Stylish/Step/Imports/Tests.hs
+++ b/tests/Language/Haskell/Stylish/Step/Imports/Tests.hs
@@ -47,6 +47,11 @@ tests = testGroup "Language.Haskell.Stylish.Step.Imports.Tests"
, testCase "case 19d" case19c
, testCase "case 19d" case19d
, testCase "case 20" case20
+ , testCase "case 21" case21
+ , testCase "case 22" case22
+ , testCase "case 23" case23
+ , testCase "case 24" case24
+ , testCase "case 25" case25
]
@@ -186,7 +191,7 @@ case07 = expected @=? testStep (step 80 $ fromImportAlign File) input'
--------------------------------------------------------------------------------
case08 :: Assertion
case08 = expected
- @=? testStep (step 80 $ Options Global WithAlias Inline Inherit (LPConstant 4) True) input
+ @=? testStep (step 80 $ Options Global WithAlias True Inline Inherit (LPConstant 4) True False) input
where
expected = unlines
[ "module Herp where"
@@ -209,7 +214,7 @@ case08 = expected
--------------------------------------------------------------------------------
case09 :: Assertion
case09 = expected
- @=? testStep (step 80 $ Options Global WithAlias Multiline Inherit (LPConstant 4) True) input
+ @=? testStep (step 80 $ Options Global WithAlias True Multiline Inherit (LPConstant 4) True False) input
where
expected = unlines
[ "module Herp where"
@@ -243,7 +248,7 @@ case09 = expected
--------------------------------------------------------------------------------
case10 :: Assertion
case10 = expected
- @=? testStep (step 40 $ Options Group WithAlias Multiline Inherit (LPConstant 4) True) input
+ @=? testStep (step 40 $ Options Group WithAlias True Multiline Inherit (LPConstant 4) True False) input
where
expected = unlines
[ "module Herp where"
@@ -282,7 +287,7 @@ case10 = expected
--------------------------------------------------------------------------------
case11 :: Assertion
case11 = expected
- @=? testStep (step 80 $ Options Group NewLine Inline Inherit (LPConstant 4) True) input
+ @=? testStep (step 80 $ Options Group NewLine True Inline Inherit (LPConstant 4) True False) input
where
expected = unlines
[ "module Herp where"
@@ -310,7 +315,7 @@ case11 = expected
--------------------------------------------------------------------------------
case12 :: Assertion
case12 = expected
- @=? testStep (step 80 $ Options Group NewLine Inline Inherit (LPConstant 2) True) input'
+ @=? testStep (step 80 $ Options Group NewLine True Inline Inherit (LPConstant 2) True False) input'
where
input' = unlines
[ "import Data.List (map)"
@@ -325,7 +330,7 @@ case12 = expected
--------------------------------------------------------------------------------
case13 :: Assertion
case13 = expected
- @=? testStep (step 80 $ Options None WithAlias InlineWithBreak Inherit (LPConstant 4) True) input'
+ @=? testStep (step 80 $ Options None WithAlias True InlineWithBreak Inherit (LPConstant 4) True False) input'
where
input' = unlines
[ "import qualified Data.List as List (concat, foldl, foldr, head, init,"
@@ -343,7 +348,7 @@ case13 = expected
case14 :: Assertion
case14 = expected
@=? testStep
- (step 80 $ Options None WithAlias InlineWithBreak Inherit (LPConstant 10) True) expected
+ (step 80 $ Options None WithAlias True InlineWithBreak Inherit (LPConstant 10) True False) expected
where
expected = unlines
[ "import qualified Data.List as List (concat, map, null, reverse, tail, (++))"
@@ -353,7 +358,7 @@ case14 = expected
--------------------------------------------------------------------------------
case15 :: Assertion
case15 = expected
- @=? testStep (step 80 $ Options None AfterAlias Multiline Inherit (LPConstant 4) True) input'
+ @=? testStep (step 80 $ Options None AfterAlias True Multiline Inherit (LPConstant 4) True False) input'
where
expected = unlines
[ "import Data.Acid (AcidState)"
@@ -379,7 +384,7 @@ case15 = expected
--------------------------------------------------------------------------------
case16 :: Assertion
case16 = expected
- @=? testStep (step 80 $ Options None AfterAlias Multiline Inherit (LPConstant 4) False) input'
+ @=? testStep (step 80 $ Options None AfterAlias True Multiline Inherit (LPConstant 4) False False) input'
where
expected = unlines
[ "import Data.Acid (AcidState)"
@@ -403,7 +408,7 @@ case16 = expected
--------------------------------------------------------------------------------
case17 :: Assertion
case17 = expected
- @=? testStep (step 80 $ Options None AfterAlias Multiline Inherit (LPConstant 4) True) input'
+ @=? testStep (step 80 $ Options None AfterAlias True Multiline Inherit (LPConstant 4) True False) input'
where
expected = unlines
[ "import Control.Applicative (Applicative (pure, (<*>)))"
@@ -421,7 +426,7 @@ case17 = expected
--------------------------------------------------------------------------------
case18 :: Assertion
case18 = expected @=? testStep
- (step 40 $ Options None AfterAlias InlineToMultiline Inherit (LPConstant 4) True) input'
+ (step 40 $ Options None AfterAlias True InlineToMultiline Inherit (LPConstant 4) True False) input'
where
expected = unlines
----------------------------------------
@@ -448,7 +453,7 @@ case18 = expected @=? testStep
--------------------------------------------------------------------------------
case19 :: Assertion
case19 = expected @=? testStep
- (step 40 $ Options Global NewLine InlineWithBreak RightAfter (LPConstant 17) True) case19input
+ (step 40 $ Options Global NewLine True InlineWithBreak RightAfter (LPConstant 17) True False) case19input
where
expected = unlines
----------------------------------------
@@ -463,7 +468,7 @@ case19 = expected @=? testStep
case19b :: Assertion
case19b = expected @=? testStep
- (step 40 $ Options File NewLine InlineWithBreak RightAfter (LPConstant 17) True) case19input
+ (step 40 $ Options File NewLine True InlineWithBreak RightAfter (LPConstant 17) True False) case19input
where
expected = unlines
----------------------------------------
@@ -478,7 +483,7 @@ case19b = expected @=? testStep
case19c :: Assertion
case19c = expected @=? testStep
- (step 40 $ Options File NewLine InlineWithBreak RightAfter LPModuleName True) case19input
+ (step 40 $ Options File NewLine True InlineWithBreak RightAfter LPModuleName True False) case19input
where
expected = unlines
----------------------------------------
@@ -493,7 +498,7 @@ case19c = expected @=? testStep
case19d :: Assertion
case19d = expected @=? testStep
- (step 40 $ Options Global NewLine InlineWithBreak RightAfter LPModuleName True) case19input
+ (step 40 $ Options Global NewLine True InlineWithBreak RightAfter LPModuleName True False) case19input
where
expected = unlines
----------------------------------------
@@ -531,3 +536,130 @@ case20 = expected
, "import qualified Data.Map as Map"
, "import Data.Set (empty)"
]
+
+--------------------------------------------------------------------------------
+case21 :: Assertion
+case21 = expected
+ @=? testStep (step 80 defaultOptions) input'
+ where
+ expected = unlines
+ [ "{-# LANGUAGE ExplicitNamespaces #-}"
+ , "import X1 (A, B, C)"
+ , "import X2 (A, B, C)"
+ , "import X3 (A (..))"
+ , "import X4 (A (..))"
+ , "import X5 (A (..))"
+ , "import X6 (A (a, b, c), B (m, n, o))"
+ , "import X7 (a, b, c)"
+ , "import X8 (type (+), (+))"
+ , "import X9 hiding (x, y, z)"
+ ]
+ input' = unlines
+ [ "{-# LANGUAGE ExplicitNamespaces #-}"
+ , "import X1 (A, B, A, C, A, B, A)"
+ , "import X2 (C(), B(), A())"
+ , "import X3 (A(..))"
+ , "import X4 (A, A(..))"
+ , "import X5 (A(..), A(x))"
+ , "import X6 (A(a,b), B(m,n), A(c), B(o))"
+ , "import X7 (a, b, a, c)"
+ , "import X8 (type (+), (+))"
+ , "import X9 hiding (x, y, z, x)"
+ ]
+
+--------------------------------------------------------------------------------
+case22 :: Assertion
+case22 = expected
+ @=? testStep (step 80 defaultOptions) input'
+ where
+ expected = unlines
+ [ "{-# LANGUAGE PackageImports #-}"
+ , "import A"
+ , "import \"blah\" A"
+ , "import \"foo\" A"
+ , "import qualified \"foo\" A as X"
+ , "import \"foo\" B (shortName, someLongName, someLongerName,"
+ , " theLongestNameYet)"
+ ]
+ input' = unlines
+ [ "{-# LANGUAGE PackageImports #-}"
+ , "import A"
+ , "import \"foo\" A"
+ , "import \"blah\" A"
+ , "import qualified \"foo\" A as X"
+ -- this import fits into 80 chats without "foo",
+ -- but doesn't fit when "foo" is included into the calculation
+ , "import \"foo\" B (someLongName, someLongerName, " ++
+ "theLongestNameYet, shortName)"
+ ]
+
+--------------------------------------------------------------------------------
+case23 :: Assertion
+case23 = expected
+ @=? testStep (step 40 $ Options None AfterAlias False Inline Inherit (LPConstant 4) True True) input'
+ where
+ expected = unlines
+ [ "import Data.Acid ( AcidState )"
+ , "import Data.Default.Class ( Default (def) )"
+ , ""
+ , "import Data.Monoid ( (<>) )"
+ , ""
+ , "import Data.ALongName.Foo ( Boo, Foo,"
+ , " Goo )"
+ ]
+
+ input' = unlines
+ [ "import Data.Acid (AcidState)"
+ , "import Data.Default.Class (Default(def))"
+ , ""
+ , "import Data.Monoid ((<>) )"
+ , ""
+ , "import Data.ALongName.Foo (Foo, Goo, Boo)"
+ ]
+
+--------------------------------------------------------------------------------
+case24 :: Assertion
+case24 = expected
+ @=? testStep (step 40 $ Options None AfterAlias False InlineWithBreak Inherit (LPConstant 4) True True) input'
+ where
+ expected = unlines
+ [ "import Data.Acid ( AcidState )"
+ , "import Data.Default.Class"
+ , " ( Default (def) )"
+ , ""
+ , "import Data.ALongName.Foo"
+ , " ( BooReallyLong, FooReallyLong,"
+ , " GooReallyLong )"
+ ]
+
+ input' = unlines
+ [ "import Data.Acid (AcidState)"
+ , "import Data.Default.Class (Default(def))"
+ , ""
+ , "import Data.ALongName.Foo (FooReallyLong, " ++
+ "GooReallyLong, BooReallyLong)"
+ ]
+
+--------------------------------------------------------------------------------
+case25 :: Assertion
+case25 = expected
+ @=? testStep (step 80 $ Options Group AfterAlias False Multiline Inherit (LPConstant 4) False False) input'
+ where
+ expected = unlines
+ [ "import Data.Acid (AcidState)"
+ , "import Data.Default.Class (Default(def))"
+ , ""
+ , "import Data.Maybe (Maybe(Just, Nothing))"
+ , "import qualified Data.Maybe.Extra (Maybe(Just, Nothing))"
+ , ""
+ , "import Data.Foo (Foo(Bar, Foo), Goo(Goo))"
+ ]
+ input' = unlines
+ [ "import Data.Acid (AcidState)"
+ , "import Data.Default.Class (Default(def))"
+ , ""
+ , "import Data.Maybe (Maybe (Just, Nothing))"
+ , "import qualified Data.Maybe.Extra (Maybe(Just, Nothing))"
+ , ""
+ , "import Data.Foo (Foo (Foo,Bar), Goo(Goo))"
+ ]