Skip to content

Commit

Permalink
Add new step Signature that will format function signatures
Browse files Browse the repository at this point in the history
The step is a NOP still but additional tests were already created
specifing how we anticipate the step to behave. This step is heavily
inspired by https://github.com/input-output-hk/ouroboros-network/blob/bf8579cc2ff2a7bc4ba23150eff659cfd1c6ccca/ouroboros-consensus/docs/StyleGuide.md
  • Loading branch information
EncodePanda committed Feb 3, 2021
1 parent 03b34d3 commit 2b80feb
Show file tree
Hide file tree
Showing 4 changed files with 159 additions and 0 deletions.
10 changes: 10 additions & 0 deletions lib/Language/Haskell/Stylish/Step/Signature.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
module Language.Haskell.Stylish.Step.Signature where

import Language.Haskell.Stylish.Step

data Config = Config
{ maxColumnLength :: Int
}

step :: Config -> Step
step _ = makeStep "Signature" (\ls _ -> ls)
3 changes: 3 additions & 0 deletions stylish-haskell.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,7 @@ Library
Language.Haskell.Stylish.Step.Imports
Language.Haskell.Stylish.Step.ModuleHeader
Language.Haskell.Stylish.Step.LanguagePragmas
Language.Haskell.Stylish.Step.Signature
Language.Haskell.Stylish.Step.SimpleAlign
Language.Haskell.Stylish.Step.Squash
Language.Haskell.Stylish.Step.Tabs
Expand Down Expand Up @@ -137,6 +138,8 @@ Test-suite stylish-haskell-tests
Language.Haskell.Stylish.Step.ModuleHeader.Tests
Language.Haskell.Stylish.Step.LanguagePragmas
Language.Haskell.Stylish.Step.LanguagePragmas.Tests
Language.Haskell.Stylish.Step.Signature
Language.Haskell.Stylish.Step.Signature.Tests
Language.Haskell.Stylish.Step.SimpleAlign
Language.Haskell.Stylish.Step.SimpleAlign.Tests
Language.Haskell.Stylish.Step.Squash
Expand Down
144 changes: 144 additions & 0 deletions tests/Language/Haskell/Stylish/Step/Signature/Tests.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,144 @@
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
module Language.Haskell.Stylish.Step.Signature.Tests
( tests
) where

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

tests :: Test
tests = testGroup "Language.Haskell.Stylish.Step.Signature.Tests"
[ testCase "do not wrap signature if it fits max column length" case00
-- , testCase "wrap signature if it does not fit max column length" case01
-- , testCase "how it behaves when there is a list of constraints" case02
-- , testCase "how it behaves when there is a explicit forall" case03
-- , testCase "how it behaves when there is a explicit forall" case04
-- , testCase "how it behaves when there is a large function in the argument" case05
]

config :: Int -> Config
config maxColumnLength = Config
{ maxColumnLength = maxColumnLength
}

case00 :: Assertion
case00 = expected @=? testStep (step $ config 80) input
where
input = unlines
[ "module Herp where"
, ""
, "fooBar :: a -> b -> a"
, "fooBar v _ = v"
]
expected = input

case01 :: Assertion
case01 = expected @=? testStep (step $ config 20) input
where
input = unlines
[ "module Herp where"
, ""
, "fooBar :: a -> b -> a"
, "fooBar v _ = v"
]
expected = unlines
[ "module Herp where"
, ""
, "fooBar ::"
, " a"
, " -> b"
, " -> a"
, "fooBar v _ = v"
]

case02 :: Assertion
case02 = expected @=? testStep (step $ config 20) input
where
input = unlines
[ "module Herp where"
, ""
, "fooBar :: (Eq a, Show b) => a -> b -> a"
, "fooBar v _ = v"
]
expected = unlines
[ "module Herp where"
, ""
, "fooBar ::"
, " (Eq a, Show b)"
, " => a"
, " -> b"
, " -> a"
, "fooBar v _ = v"
]

case03 :: Assertion
case03 = expected @=? testStep (step $ config 20) input
where
input = unlines
[ "module Herp where"
, ""
, "fooBar :: forall a . b. (Eq a, Show b) => a -> b -> a"
, "fooBar v _ = v"
]
expected = unlines
[ "module Herp where"
, ""
, "fooBar ::"
, " forall a . b."
, " (Eq a, Show b)"
, " => a"
, " -> b"
, " -> a"
, "fooBar v _ = v"
]

case04 :: Assertion
case04 = expected @=? testStep (step $ config 20) input
where
input = unlines
[ "module Herp where"
, ""
, "fooBar :: forall a . b. c. (Eq a, Show b, Ord c) => a -> b -> c -> a"
, "fooBar v _ _ = v"
]
expected = unlines
[ "module Herp where"
, ""
, "fooBar ::"
, " forall a . b. ("
, " Eq a"
, " , Show b"
, " , Ord c)"
, " )"
, " => a"
, " -> b"
, " -> a"
, "fooBar v _ = v"
]

case05 :: Assertion
case05 = expected @=? testStep (step $ config 20) input
where
input = unlines
[ "module Herp where"
, ""
, "fooBar :: => a -> (forall c. Eq c => c -> a -> a) -> a"
, "fooBar v _ = v"
]
expected = unlines
[ "module Herp where"
, ""
, "fooBar ::"
, " => a"
, " -> ( forall c. Eq c"
, " => c"
, " -> a"
, " -> a"
, " )"
, " -> a"
, "fooBar v _ = v"
]
2 changes: 2 additions & 0 deletions tests/TestSuite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ import qualified Language.Haskell.Stylish.Step.Imports.Tests
import qualified Language.Haskell.Stylish.Step.Imports.FelixTests
import qualified Language.Haskell.Stylish.Step.ModuleHeader.Tests
import qualified Language.Haskell.Stylish.Step.LanguagePragmas.Tests
import qualified Language.Haskell.Stylish.Step.Signature.Tests
import qualified Language.Haskell.Stylish.Step.SimpleAlign.Tests
import qualified Language.Haskell.Stylish.Step.Squash.Tests
import qualified Language.Haskell.Stylish.Step.Tabs.Tests
Expand All @@ -34,6 +35,7 @@ main = defaultMain
, Language.Haskell.Stylish.Step.Imports.FelixTests.tests
, Language.Haskell.Stylish.Step.LanguagePragmas.Tests.tests
, Language.Haskell.Stylish.Step.ModuleHeader.Tests.tests
, Language.Haskell.Stylish.Step.Signature.Tests.tests
, Language.Haskell.Stylish.Step.SimpleAlign.Tests.tests
, Language.Haskell.Stylish.Step.Squash.Tests.tests
, Language.Haskell.Stylish.Step.Tabs.Tests.tests
Expand Down

0 comments on commit 2b80feb

Please sign in to comment.