Skip to content

Commit 41dcda2

Browse files
authored
Disable formatting of data types without records (#265)
1 parent d259440 commit 41dcda2

File tree

3 files changed

+28
-10
lines changed

3 files changed

+28
-10
lines changed

lib/Language/Haskell/Stylish/Step/Data.hs

Lines changed: 8 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -45,9 +45,15 @@ commentsWithin lb = filter within
4545

4646
changeDecl :: [Comment] -> Int -> H.Decl LineBlock -> Maybe ChangeLine
4747
changeDecl _ _ (H.DataDecl _ (H.DataType _) Nothing _ [] _) = Nothing
48-
changeDecl allComments indentSize (H.DataDecl block (H.DataType _) Nothing dhead decls derivings) =
49-
Just $ change block (const $ concat newLines)
48+
changeDecl allComments indentSize (H.DataDecl block (H.DataType _) Nothing dhead decls derivings)
49+
| hasRecordFields = Just $ change block (const $ concat newLines)
50+
| otherwise = Nothing
5051
where
52+
hasRecordFields = any
53+
(\qual -> case qual of
54+
(H.QualConDecl _ _ _ (H.RecDecl {})) -> True
55+
_ -> False)
56+
decls
5157
newLines = fmap constructors zipped ++ [fmap (indented . H.prettyPrint) derivings]
5258
zipped = zip decls ([1..] ::[Int])
5359
constructors (decl, 1) = processConstructor allComments typeConstructor indentSize decl

tests/Language/Haskell/Stylish/Step/Data/Tests.hs

Lines changed: 14 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ tests = testGroup "Language.Haskell.Stylish.Step.Data.Tests"
3030
, testCase "case 17" case17
3131
, testCase "case 18" case18
3232
, testCase "case 19" case19
33+
, testCase "case 20 (issue 262)" case20
3334
]
3435

3536
case00 :: Assertion
@@ -155,19 +156,14 @@ case07 = expected @=? testStep (step 2) input
155156
expected = input
156157

157158
case08 :: Assertion
158-
case08 = expected @=? testStep (step 2) input
159+
case08 = input @=? testStep (step 2) input
159160
where
160161
input = unlines
161162
[ "module Herp where"
162163
, ""
163164
, "data Phantom a ="
164165
, " Phantom"
165166
]
166-
expected = unlines
167-
[ "module Herp where"
168-
, ""
169-
, "data Phantom a = Phantom"
170-
]
171167

172168
case09 :: Assertion
173169
case09 = expected @=? testStep (step 4) input
@@ -389,3 +385,15 @@ case19 = expected @=? testStep (step 2) input
389385
, " , age :: Int"
390386
, " }"
391387
]
388+
389+
-- | Should not break Enums (data without records) formating
390+
--
391+
-- See https://github.com/jaspervdj/stylish-haskell/issues/262
392+
case20 :: Assertion
393+
case20 = input @=? testStep (step 2) input
394+
where
395+
input = unlines
396+
[ "module Herp where"
397+
, ""
398+
, "data Tag = Title | Text deriving (Eq, Show)"
399+
]

tests/Language/Haskell/Stylish/Tests.hs

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -28,10 +28,12 @@ tests = testGroup "Language.Haskell.Stylish.Step.Tabs.Tests"
2828
case01 :: Assertion
2929
case01 = (@?= result) =<< format Nothing Nothing input
3030
where
31-
input = "module Herp where\n data Foo = Bar | Baz"
31+
input = "module Herp where\ndata Foo = Bar | Baz { baz :: Int }"
3232
result = Right [ "module Herp where"
3333
, "data Foo = Bar"
3434
, " | Baz"
35+
, " { baz :: Int"
36+
, " }"
3537
]
3638

3739

@@ -47,10 +49,12 @@ case02 = withTestDirTree $ do
4749
actual <- format (Just $ ConfigPath "test-config.yaml") Nothing input
4850
actual @?= result
4951
where
50-
input = "module Herp where\n data Foo = Bar | Baz"
52+
input = "module Herp where\ndata Foo = Bar | Baz { baz :: Int }"
5153
result = Right [ "module Herp where"
5254
, "data Foo = Bar"
5355
, " | Baz"
56+
, " { baz :: Int"
57+
, " }"
5458
]
5559

5660

0 commit comments

Comments
 (0)