summaryrefslogtreecommitdiffhomepage
path: root/tests/Language/Haskell/Stylish/Step/SimpleAlign/Tests.hs
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Language/Haskell/Stylish/Step/SimpleAlign/Tests.hs')
-rw-r--r--tests/Language/Haskell/Stylish/Step/SimpleAlign/Tests.hs338
1 files changed, 227 insertions, 111 deletions
diff --git a/tests/Language/Haskell/Stylish/Step/SimpleAlign/Tests.hs b/tests/Language/Haskell/Stylish/Step/SimpleAlign/Tests.hs
index a2a51fc..e30f0ba 100644
--- a/tests/Language/Haskell/Stylish/Step/SimpleAlign/Tests.hs
+++ b/tests/Language/Haskell/Stylish/Step/SimpleAlign/Tests.hs
@@ -1,4 +1,5 @@
--------------------------------------------------------------------------------
+{-# LANGUAGE OverloadedLists #-}
module Language.Haskell.Stylish.Step.SimpleAlign.Tests
( tests
) where
@@ -7,7 +8,7 @@ module Language.Haskell.Stylish.Step.SimpleAlign.Tests
--------------------------------------------------------------------------------
import Test.Framework (Test, testGroup)
import Test.Framework.Providers.HUnit (testCase)
-import Test.HUnit (Assertion, (@=?))
+import Test.HUnit (Assertion)
--------------------------------------------------------------------------------
@@ -27,81 +28,74 @@ tests = testGroup "Language.Haskell.Stylish.Step.SimpleAlign.Tests"
, testCase "case 07" case07
, testCase "case 08" case08
, testCase "case 09" case09
+ , testCase "case 10" case10
+ , testCase "case 11" case11
+ , testCase "case 12" case12
+ , testCase "case 13" case13
+ , testCase "case 13b" case13b
+ , testCase "case 14" case14
+ , testCase "case 15" case15
+ , testCase "case 16" case16
+ , testCase "case 17" case17
]
--------------------------------------------------------------------------------
case01 :: Assertion
-case01 = expected @=? testStep (step (Just 80) defaultConfig) input
- where
- input = unlines
- [ "eitherToMaybe e = case e of"
- , " Left _ -> Nothing"
- , " Right x -> Just x"
- ]
-
- expected = unlines
- [ "eitherToMaybe e = case e of"
- , " Left _ -> Nothing"
- , " Right x -> Just x"
- ]
+case01 = assertSnippet (step (Just 80) defaultConfig)
+ [ "eitherToMaybe e = case e of"
+ , " Left _ -> Nothing"
+ , " Right x -> Just x"
+ ]
+ [ "eitherToMaybe e = case e of"
+ , " Left _ -> Nothing"
+ , " Right x -> Just x"
+ ]
--------------------------------------------------------------------------------
case02 :: Assertion
-case02 = expected @=? testStep (step (Just 80) defaultConfig) input
- where
- input = unlines
- [ "eitherToMaybe (Left _) = Nothing"
- , "eitherToMaybe (Right x) = Just x"
- ]
-
- expected = unlines
- [ "eitherToMaybe (Left _) = Nothing"
- , "eitherToMaybe (Right x) = Just x"
- ]
+case02 = assertSnippet (step (Just 80) defaultConfig)
+ [ "eitherToMaybe (Left _) = Nothing"
+ , "eitherToMaybe (Right x) = Just x"
+ ]
+ [ "eitherToMaybe (Left _) = Nothing"
+ , "eitherToMaybe (Right x) = Just x"
+ ]
--------------------------------------------------------------------------------
case03 :: Assertion
-case03 = expected @=? testStep (step (Just 80) defaultConfig) input
- where
- input = unlines
- [ "heady def [] = def"
- , "heady _ (x : _) = x"
- ]
-
- expected = unlines
- [ "heady def [] = def"
- , "heady _ (x : _) = x"
- ]
+case03 = assertSnippet (step (Just 80) defaultConfig)
+ [ "heady def [] = def"
+ , "heady _ (x : _) = x"
+ ]
+ [ "heady def [] = def"
+ , "heady _ (x : _) = x"
+ ]
--------------------------------------------------------------------------------
case04 :: Assertion
-case04 = expected @=? testStep (step (Just 80) defaultConfig) input
- where
- input = unlines
- [ "data Foo = Foo"
- , " { foo :: Int"
- , " , barqux :: String"
- , " } deriving (Show)"
- ]
-
- expected = unlines
- [ "data Foo = Foo"
- , " { foo :: Int"
- , " , barqux :: String"
- , " } deriving (Show)"
- ]
+case04 = assertSnippet (step (Just 80) defaultConfig)
+ [ "data Foo = Foo"
+ , " { foo :: Int"
+ , " , barqux :: String"
+ , " } deriving (Show)"
+ ]
+ [ "data Foo = Foo"
+ , " { foo :: Int"
+ , " , barqux :: String"
+ , " } deriving (Show)"
+ ]
--------------------------------------------------------------------------------
case05 :: Assertion
-case05 = input @=? testStep (step (Just 80) defaultConfig) input
+case05 = assertSnippet (step (Just 80) defaultConfig) input input
where
-- Don't attempt to align this since a field spans multiple lines
- input = unlines
+ input =
[ "data Foo = Foo"
, " { foo :: Int"
, " , barqux"
@@ -112,78 +106,200 @@ case05 = input @=? testStep (step (Just 80) defaultConfig) input
--------------------------------------------------------------------------------
case06 :: Assertion
-case06 =
+case06 = assertSnippet
-- 22 max columns is /just/ enough to align this stuff.
- expected @=? testStep (step (Just 22) defaultConfig) input
- where
- input = unlines
- [ "data Foo = Foo"
- , " { foo :: String"
- , " , barqux :: Int"
- , " }"
- ]
-
- expected = unlines
- [ "data Foo = Foo"
- , " { foo :: String"
- , " , barqux :: Int"
- , " }"
- ]
+ (step (Just 22) defaultConfig)
+ [ "data Foo = Foo"
+ , " { foo :: String"
+ , " , barqux :: Int"
+ , " }"
+ ]
+ [ "data Foo = Foo"
+ , " { foo :: String"
+ , " , barqux :: Int"
+ , " }"
+ ]
--------------------------------------------------------------------------------
case07 :: Assertion
-case07 =
+case07 = assertSnippet
-- 21 max columns is /just NOT/ enough to align this stuff.
- expected @=? testStep (step (Just 21) defaultConfig) input
- where
- input = unlines
- [ "data Foo = Foo"
- , " { foo :: String"
- , " , barqux :: Int"
- , " }"
- ]
-
- expected = unlines
- [ "data Foo = Foo"
- , " { foo :: String"
- , " , barqux :: Int"
- , " }"
- ]
+ (step (Just 21) defaultConfig)
+ [ "data Foo = Foo"
+ , " { foo :: String"
+ , " , barqux :: Int"
+ , " }"
+ ]
+ [ "data Foo = Foo"
+ , " { foo :: String"
+ , " , barqux :: Int"
+ , " }"
+ ]
--------------------------------------------------------------------------------
case08 :: Assertion
-case08 = expected @=? testStep (step (Just 80) defaultConfig) input
- where
- input = unlines
- [ "canDrink mbAge = case mbAge of"
- , " Just age | age > 18 -> True"
- , " _ -> False"
- ]
-
- expected = unlines
- [ "canDrink mbAge = case mbAge of"
- , " Just age | age > 18 -> True"
- , " _ -> False"
- ]
+case08 = assertSnippet (step (Just 80) defaultConfig)
+ [ "canDrink mbAge = case mbAge of"
+ , " Just age | age > 18 -> True"
+ , " _ -> False"
+ ]
+ [ "canDrink mbAge = case mbAge of"
+ , " Just age | age > 18 -> True"
+ , " _ -> False"
+ ]
--------------------------------------------------------------------------------
case09 :: Assertion
-case09 =
- expected @=? testStep (step Nothing defaultConfig) input
+case09 = assertSnippet (step Nothing defaultConfig)
+ [ "data Foo = Foo"
+ , " { foo :: String"
+ , " , barqux :: Int"
+ , " }"
+ ]
+ [ "data Foo = Foo"
+ , " { foo :: String"
+ , " , barqux :: Int"
+ , " }"
+ ]
+
+
+--------------------------------------------------------------------------------
+case10 :: Assertion
+case10 = assertSnippet (step Nothing defaultConfig)
+ [ "padQual = case align' of"
+ , " Global -> True"
+ , " File -> fileAlign"
+ , " Group -> anyQual"
+ ]
+ [ "padQual = case align' of"
+ , " Global -> True"
+ , " File -> fileAlign"
+ , " Group -> anyQual"
+ ]
+
+
+--------------------------------------------------------------------------------
+case11 :: Assertion
+case11 = assertSnippet (step Nothing defaultConfig)
+ [ "data Foo = Foo"
+ , " { foo :: String"
+ , " , barqux :: !Int"
+ , " }"
+ ]
+ [ "data Foo = Foo"
+ , " { foo :: String"
+ , " , barqux :: !Int"
+ , " }"
+ ]
+
+
+--------------------------------------------------------------------------------
+case12 :: Assertion
+case12 = assertSnippet (step Nothing defaultConfig { cCases = Never }) input input
where
- input = unlines
- [ "data Foo = Foo"
- , " { foo :: String"
- , " , barqux :: Int"
- , " }"
+ input =
+ [ "case x of"
+ , " Just y -> 1"
+ , " Nothing -> 2"
]
- expected = unlines
- [ "data Foo = Foo"
- , " { foo :: String"
- , " , barqux :: Int"
- , " }"
- ]
+
+--------------------------------------------------------------------------------
+case13 :: Assertion
+case13 = assertSnippet (step Nothing defaultConfig)
+ [ "cond n = if"
+ , " | n < 10, x <- 1 -> x"
+ , " | otherwise -> 2"
+ ]
+ [ "cond n = if"
+ , " | n < 10, x <- 1 -> x"
+ , " | otherwise -> 2"
+ ]
+
+case13b :: Assertion
+case13b = assertSnippet (step Nothing defaultConfig {cMultiWayIf = Never})
+ [ "cond n = if"
+ , " | n < 10, x <- 1 -> x"
+ , " | otherwise -> 2"
+ ]
+ [ "cond n = if"
+ , " | n < 10, x <- 1 -> x"
+ , " | otherwise -> 2"
+ ]
+
+
+--------------------------------------------------------------------------------
+case14 :: Assertion
+case14 = assertSnippet (step (Just 80) defaultConfig { cCases = Adjacent })
+ [ "catch e = case e of"
+ , " Left GoodError -> 1"
+ , " Left BadError -> 2"
+ , " -- otherwise"
+ , " Right [] -> 0"
+ , " Right (x:_) -> x"
+ ]
+ [ "catch e = case e of"
+ , " Left GoodError -> 1"
+ , " Left BadError -> 2"
+ , " -- otherwise"
+ , " Right [] -> 0"
+ , " Right (x:_) -> x"
+ ]
+
+
+--------------------------------------------------------------------------------
+case15 :: Assertion
+case15 = assertSnippet (step (Just 80) defaultConfig { cTopLevelPatterns = Adjacent })
+ [ "catch (Left GoodError) = 1"
+ , "catch (Left BadError) = 2"
+ , "-- otherwise"
+ , "catch (Right []) = 0"
+ , "catch (Right (x:_)) = x"
+ ]
+ [ "catch (Left GoodError) = 1"
+ , "catch (Left BadError) = 2"
+ , "-- otherwise"
+ , "catch (Right []) = 0"
+ , "catch (Right (x:_)) = x"
+ ]
+
+
+--------------------------------------------------------------------------------
+case16 :: Assertion
+case16 = assertSnippet (step (Just 80) defaultConfig { cRecords = Adjacent })
+ [ "data Foo = Foo"
+ , " { foo :: Int"
+ , " , foo2 :: String"
+ , " -- a comment"
+ , " , barqux :: String"
+ , " , baz :: String"
+ , " , baz2 :: Bool"
+ , " } deriving (Show)"
+ ]
+ [ "data Foo = Foo"
+ , " { foo :: Int"
+ , " , foo2 :: String"
+ , " -- a comment"
+ , " , barqux :: String"
+ , " , baz :: String"
+ , " , baz2 :: Bool"
+ , " } deriving (Show)"
+ ]
+
+
+--------------------------------------------------------------------------------
+case17 :: Assertion
+case17 = assertSnippet (step Nothing defaultConfig { cMultiWayIf = Adjacent })
+ [ "cond n = if"
+ , " | n < 10, x <- 1 -> x"
+ , " -- comment"
+ , " | otherwise -> 2"
+ ]
+ [ "cond n = if"
+ , " | n < 10, x <- 1 -> x"
+ , " -- comment"
+ , " | otherwise -> 2"
+ ]