summaryrefslogtreecommitdiffhomepage
path: root/tests/Language/Haskell/Stylish/Tests.hs
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Language/Haskell/Stylish/Tests.hs')
-rw-r--r--tests/Language/Haskell/Stylish/Tests.hs67
1 files changed, 47 insertions, 20 deletions
diff --git a/tests/Language/Haskell/Stylish/Tests.hs b/tests/Language/Haskell/Stylish/Tests.hs
index e7faa9b..97eab8a 100644
--- a/tests/Language/Haskell/Stylish/Tests.hs
+++ b/tests/Language/Haskell/Stylish/Tests.hs
@@ -20,13 +20,14 @@ import Language.Haskell.Stylish.Tests.Util
--------------------------------------------------------------------------------
tests :: Test
-tests = testGroup "Language.Haskell.Stylish.Step.Tabs.Tests"
+tests = testGroup "Language.Haskell.Stylish.Tests"
[ testCase "case 01" case01
, testCase "case 02" case02
, testCase "case 03" case03
, testCase "case 04" case04
, testCase "case 05" case05
, testCase "case 06" case06
+ , testCase "case 07" case07
]
@@ -35,12 +36,7 @@ case01 :: Assertion
case01 = (@?= result) =<< format Nothing Nothing input
where
input = "module Herp where\ndata Foo = Bar | Baz { baz :: Int }"
- result = Right [ "module Herp where"
- , "data Foo = Bar"
- , " | Baz"
- , " { baz :: Int"
- , " }"
- ]
+ result = Right $ lines input
--------------------------------------------------------------------------------
@@ -48,8 +44,11 @@ case02 :: Assertion
case02 = withTestDirTree $ do
writeFile "test-config.yaml" $ unlines
[ "steps:"
- , " - records: {}"
- , "indent: 2"
+ , " - records:"
+ , " equals: \"indent 2\""
+ , " first_field: \"indent 2\""
+ , " field_comment: 2"
+ , " deriving: 2"
]
actual <- format (Just $ ConfigPath "test-config.yaml") Nothing input
@@ -57,16 +56,44 @@ case02 = withTestDirTree $ do
where
input = "module Herp where\ndata Foo = Bar | Baz { baz :: Int }"
result = Right [ "module Herp where"
- , "data Foo = Bar"
+ , "data Foo"
+ , " = Bar"
, " | Baz"
- , " { baz :: Int"
- , " }"
+ , " { baz :: Int"
+ , " }"
]
-
--------------------------------------------------------------------------------
case03 :: Assertion
-case03 = (@?= result) =<< format Nothing (Just fileLocation) input
+case03 = withTestDirTree $ do
+ writeFile "test-config.yaml" $ unlines
+ [ "steps:"
+ , " - records:"
+ , " equals: \"same_line\""
+ , " first_field: \"same_line\""
+ , " field_comment: 2"
+ , " deriving: 2"
+ ]
+
+ actual <- format (Just $ ConfigPath "test-config.yaml") Nothing input
+ actual @?= result
+ where
+ input = unlines [ "module Herp where"
+ , "data Foo"
+ , " = Bar"
+ , " | Baz"
+ , " { baz :: Int"
+ , " }"
+ ]
+ result = Right [ "module Herp where"
+ , "data Foo = Bar"
+ , " | Baz { baz :: Int"
+ , " }"
+ ]
+
+--------------------------------------------------------------------------------
+case04 :: Assertion
+case04 = (@?= result) =<< format Nothing (Just fileLocation) input
where
fileLocation = "directory/File.hs"
input = "module Herp"
@@ -78,8 +105,8 @@ case03 = (@?= result) =<< format Nothing (Just fileLocation) input
--------------------------------------------------------------------------------
-- | When providing current dir including folders and files.
-case04 :: Assertion
-case04 = withTestDirTree $ do
+case05 :: Assertion
+case05 = withTestDirTree $ do
createDirectory aDir >> writeFile c fileCont
mapM_ (flip writeFile fileCont) fs
result <- findHaskellFiles False input
@@ -95,8 +122,8 @@ case04 = withTestDirTree $ do
--------------------------------------------------------------------------------
-- | When the input item is not file, do not recurse it.
-case05 :: Assertion
-case05 = withTestDirTree $ do
+case06 :: Assertion
+case06 = withTestDirTree $ do
mapM_ (flip writeFile "") input
result <- findHaskellFiles False input
result @?= expected
@@ -107,8 +134,8 @@ case05 = withTestDirTree $ do
--------------------------------------------------------------------------------
-- | Empty input should result in empty output.
-case06 :: Assertion
-case06 = withTestDirTree $ do
+case07 :: Assertion
+case07 = withTestDirTree $ do
mapM_ (flip writeFile "") input
result <- findHaskellFiles False input
result @?= expected