summaryrefslogtreecommitdiffhomepage
path: root/tests/Language/Haskell/Stylish/Tests.hs
blob: b99e620afeafffdd86919a27f962689306909e7c (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
--------------------------------------------------------------------------------
module Language.Haskell.Stylish.Tests
    ( tests
    ) where


--------------------------------------------------------------------------------
import           Data.List                           (sort)
import           System.Directory                    (createDirectory)
import           System.FilePath                     (normalise, (</>))
import           Test.Framework                      (Test, testGroup)
import           Test.Framework.Providers.HUnit      (testCase)
import           Test.HUnit                          (Assertion, (@?=))


--------------------------------------------------------------------------------
import           Language.Haskell.Stylish
import           Language.Haskell.Stylish.Tests.Util


--------------------------------------------------------------------------------
tests :: Test
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
    ]


--------------------------------------------------------------------------------
case01 :: Assertion
case01 = (@?= result) =<< format Nothing Nothing input
  where
    input = "module Herp where\ndata Foo = Bar | Baz { baz :: Int }"
    result = Right $ lines input


--------------------------------------------------------------------------------
case02 :: Assertion
case02 = withTestDirTree $ do
    writeFile "test-config.yaml" $ unlines
        [ "steps:"
        , "  - records:"
        , "      equals: \"indent 2\""
        , "      first_field: \"indent 2\""
        , "      field_comment: 2"
        , "      deriving: 2"
        , "      via: \"indent 2\""
        ]

    actual <- format (Just $ ConfigPath "test-config.yaml") Nothing input
    actual @?= result
  where
    input = "module Herp where\ndata Foo = Bar | Baz { baz :: Int }"
    result = Right [ "module Herp where"
                   , "data Foo"
                   , "  = Bar"
                   , "  | Baz"
                   , "      { baz :: Int"
                   , "      }"
                   ]

--------------------------------------------------------------------------------
case03 :: Assertion
case03 = withTestDirTree $ do
    writeFile "test-config.yaml" $ unlines
        [ "steps:"
        , "  - records:"
        , "      equals: \"same_line\""
        , "      first_field: \"same_line\""
        , "      field_comment: 2"
        , "      deriving: 2"
        , "      via: \"indent 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"
    result = Left $
      fileLocation <> ": RealSrcSpan SrcSpanPoint \"directory/File.hs\" 2 1:" 
      <> " parse error (possibly incorrect indentation or mismatched brackets)\n"

--------------------------------------------------------------------------------
-- | When providing current dir including folders and files.
case05 :: Assertion
case05 = withTestDirTree $ do
  createDirectory aDir >> writeFile c fileCont
  mapM_ (flip writeFile fileCont) fs
  result <- findHaskellFiles False input
  sort result @?= (sort $ map normalise expected)
  where
    input    = c : fs
    fs = ["b.hs", "a.hs"]
    c  = aDir </> "c.hs"
    aDir     = "aDir"
    expected = ["a.hs", "b.hs", c]
    fileCont = ""


--------------------------------------------------------------------------------
-- | When the input item is not file, do not recurse it.
case06 :: Assertion
case06 = withTestDirTree $ do
  mapM_ (flip writeFile "") input
  result <- findHaskellFiles False input
  result @?= expected
  where
    input    = ["b.hs"]
    expected = map normalise input


--------------------------------------------------------------------------------
-- | Empty input should result in empty output.
case07 :: Assertion
case07 = withTestDirTree $ do
  mapM_ (flip writeFile "") input
  result <- findHaskellFiles False input
  result @?= expected
  where
    input    = []
    expected = input