Skip to content

Commit

Permalink
Merge pull request #287 from rbasso/hspec-pascals-triangle
Browse files Browse the repository at this point in the history
pascals-triangle: Rewrite tests to use hspec with fail-fast.
  • Loading branch information
rbasso authored Sep 15, 2016
2 parents 921a937 + 885e9d3 commit 9fc98d7
Show file tree
Hide file tree
Showing 4 changed files with 31 additions and 47 deletions.
2 changes: 1 addition & 1 deletion exercises/pascals-triangle/package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -16,4 +16,4 @@ tests:
source-dirs: test
dependencies:
- pascals-triangle
- HUnit
- hspec
15 changes: 5 additions & 10 deletions exercises/pascals-triangle/src/Example.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,7 @@
module Triangle (triangle, row) where
module Triangle (rows) where

triangle :: Integral a => [[a]]
triangle = map row [1..]
rows :: Integral a => Int -> [[a]]
rows = flip take triangle

row :: (Integral a) => a -> [a]
row n = reflect [] $ scanl choices 1 [1 .. pred n `div` 2]
where
reflect acc [] | odd n = tail acc
| otherwise = acc
reflect acc (x:xs) = x : reflect (x:acc) xs
choices z i = z * (n - i) `div` i
triangle :: Integral a => [[a]]
triangle = iterate (\x -> zipWith (+) (0 : x) (x ++ [0])) [1]
9 changes: 3 additions & 6 deletions exercises/pascals-triangle/src/Triangle.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,4 @@
module Triangle (triangle, row) where
module Triangle (rows) where

triangle :: Integral a => [[a]]
triangle = undefined

row :: Integral a => a -> [a]
row = undefined
rows :: Int -> [[Integer]]
rows = undefined
52 changes: 22 additions & 30 deletions exercises/pascals-triangle/test/Tests.hs
Original file line number Diff line number Diff line change
@@ -1,36 +1,28 @@
{-# OPTIONS_GHC -fno-warn-type-defaults #-}

import Test.HUnit (Assertion, (@=?), runTestTT, Test(..), Counts(..))
import System.Exit (ExitCode(..), exitWith)
import Triangle (row, triangle)
import Data.Foldable (for_)
import Test.Hspec (Spec, describe, it, shouldBe)
import Test.Hspec.Runner (configFastFail, defaultConfig, hspecWith)

exitProperly :: IO Counts -> IO ()
exitProperly m = do
counts <- m
exitWith $ if failures counts /= 0 || errors counts /= 0 then ExitFailure 1 else ExitSuccess

testCase :: String -> Assertion -> Test
testCase label assertion = TestLabel label (TestCase assertion)
import Triangle (rows)

main :: IO ()
main = exitProperly $ runTestTT $ TestList
[ TestList triangleTests ]
main = hspecWith defaultConfig {configFastFail = True} specs

specs :: Spec
specs = describe "pascals-triangle" $ do
describe "rows" $ for_ rowsCases rowsTest
where

rowsTest (description, n, expected) = it description assertion
where
assertion = rows n `shouldBe` expected

-- Test cases adapted from `exercism/x-common` on 2016-09-14.

triangleTests :: [Test]
triangleTests =
[ testCase "1 row" $
[[1]] @=? take 1 (triangle :: [[Int]])
, testCase "2 rows" $
[[1], [1, 1]] @=? take 2 (triangle :: [[Int]])
, testCase "3 rows" $
[[1], [1, 1], [1, 2, 1]] @=? take 3 (triangle :: [[Int]])
, testCase "4 rows" $
[[1], [1, 1], [1, 2, 1], [1, 3, 3, 1]] @=? take 4 (triangle :: [[Int]])
, testCase "5th row" $
[1, 4, 6, 4, 1] @=? (row 5 :: [Int])
, testCase "20th row" $
[(1 :: Int), 19, 171, 969, 3876, 11628, 27132, 50388, 75582, 92378
, 92378, 75582, 50388, 27132, 11628, 3876, 969, 171, 19, 1] @=? row 20
, testCase "201st row maximum" $
(product [101..200] `div` product [1..100] :: Integer) @=? row 201 !! 100
]
rowsCases = [ ("no rows" , 0, [ ])
, ("single row" , 1, [[1] ])
, ("two rows" , 2, [[1], [1, 1] ])
, ("three rows" , 3, [[1], [1, 1], [1, 2, 1] ])
, ("four rows" , 4, [[1], [1, 1], [1, 2, 1], [1, 3, 3, 1]])
, ("negative rows",-1, [ ]) ]

0 comments on commit 9fc98d7

Please sign in to comment.