Skip to content

Commit

Permalink
Closing few issues (#367)
Browse files Browse the repository at this point in the history
* Add regression test showing that issue #282 does no longer exist

* Add regression tests showing that issue #273 is fixed

* Add regression test for issue #198
  • Loading branch information
EncodePanda authored Apr 26, 2021
1 parent 4cbefb8 commit d786187
Show file tree
Hide file tree
Showing 4 changed files with 106 additions and 0 deletions.
1 change: 1 addition & 0 deletions stylish-haskell.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -147,6 +147,7 @@ Test-suite stylish-haskell-tests
Language.Haskell.Stylish.Step.TrailingWhitespace.Tests
Language.Haskell.Stylish.Step.UnicodeSyntax
Language.Haskell.Stylish.Step.UnicodeSyntax.Tests
Language.Haskell.Stylish.Regressions
Language.Haskell.Stylish.Tests
Language.Haskell.Stylish.Tests.Util
Language.Haskell.Stylish.Util
Expand Down
35 changes: 35 additions & 0 deletions tests/Language/Haskell/Stylish/Regressions.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
module Language.Haskell.Stylish.Regressions
( tests
) where

import Language.Haskell.Stylish.Step.Imports
import Language.Haskell.Stylish.Tests.Util (testStep)
import Test.Framework (Test, testGroup)
import Test.Framework.Providers.HUnit (testCase)
import Test.HUnit (Assertion, (@=?))


tests :: Test
tests = testGroup "Language.Haskell.Stylish.Regressions"
[ testCase "case 00 (#198)" case00
]
-- | Error parsing '(,) #198
--
-- See https://github.com/haskell/stylish-haskell/issues/198
case00 :: Assertion
case00 = expected @=? testStep (step (Just 80) $ importStepConfig Global) input
where
input = unlines
[ "{-# LANGUAGE TemplateHaskell #-}"
, ""
, "import Language.Haskell.TH.Syntax"
, ""
, "main = print $ showName '(,)"
]

expected = input

importStepConfig :: ImportAlign -> Options
importStepConfig align = defaultOptions { importAlign = align }
68 changes: 68 additions & 0 deletions tests/Language/Haskell/Stylish/Step/Data/Tests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -73,6 +73,8 @@ tests = testGroup "Language.Haskell.Stylish.Step.Data.Tests"
, testCase "case 58" case58
, testCase "case 59" case59
, testCase "case 60" case60
, testCase "case 61 (issue 282)" case61
, testCase "case 62 (issue 273)" case62
]

case00 :: Assertion
Expand Down Expand Up @@ -1309,6 +1311,72 @@ case60 = assertSnippet (step defaultConfig)
[ "data Foo = forall a . Bar a" ]
[ "data Foo = forall a. Bar a" ]

-- | Formatting duplicates haddock comments #282
--
-- Regression test for https://github.com/haskell/stylish-haskell/issues/282
case61 :: Assertion
case61 = expected @=? testStep (step sameIndentStyle) input
where
input = unlines
[ "module Herp where"
, ""
, "data Game = Game { _board :: Board -- ^ Board state"
, " , _time :: Int -- ^ Time elapsed"
, " , _paused :: Bool -- ^ Playing vs. paused"
, " , _speed :: Float -- ^ Speed in [0..1]"
, " , _interval :: TVar Int -- ^ Interval kept in TVar"
, " }"
]

expected = unlines
[ "module Herp where"
, ""
, "data Game = Game"
, " { _board :: Board"
, " -- ^ Board state"
, " , _time :: Int"
, " -- ^ Time elapsed"
, " , _paused :: Bool"
, " -- ^ Playing vs. paused"
, " , _speed :: Float"
, " -- ^ Speed in [0..1]"
, " , _interval :: TVar Int"
, " -- ^ Interval kept in TVar"
, " }"
]

-- | Comment issues with record formatting #273
--
-- Regression test for https://github.com/haskell/stylish-haskell/issues/273
case62 :: Assertion
case62 = expected @=? testStep (step sameIndentStyle) input
where
input = unlines
[ "module Herp where"
, ""
, "data Foo = Foo"
, " { -- | This is a comment above some line."
, " -- It can span multiple lines."
, " fooName :: String"
, " , fooAge :: Int"
, " -- ^ This is a comment below some line."
, " -- It can span multiple lines."
, " }"
]

expected = unlines
[ "module Herp where"
, ""
, "data Foo = Foo"
, " { -- | This is a comment above some line."
, " -- It can span multiple lines."
, " fooName :: String"
, " , fooAge :: Int"
, " -- ^ This is a comment below some line."
, " -- It can span multiple lines."
, " }"
]

sameSameStyle :: Config
sameSameStyle = Config SameLine SameLine 2 2 False True SameLine False True NoMaxColumns

Expand Down
2 changes: 2 additions & 0 deletions tests/TestSuite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ import qualified Language.Haskell.Stylish.Step.Tabs.Tests
import qualified Language.Haskell.Stylish.Step.TrailingWhitespace.Tests
import qualified Language.Haskell.Stylish.Step.UnicodeSyntax.Tests
import qualified Language.Haskell.Stylish.Tests
import qualified Language.Haskell.Stylish.Regressions


--------------------------------------------------------------------------------
Expand All @@ -40,4 +41,5 @@ main = defaultMain
, Language.Haskell.Stylish.Step.TrailingWhitespace.Tests.tests
, Language.Haskell.Stylish.Step.UnicodeSyntax.Tests.tests
, Language.Haskell.Stylish.Tests.tests
, Language.Haskell.Stylish.Regressions.tests
]

0 comments on commit d786187

Please sign in to comment.