Skip to content

Commit

Permalink
Extend FromRow/ToRow instance testing to longer tuples
Browse files Browse the repository at this point in the history
  • Loading branch information
nurpax committed Apr 6, 2014
1 parent 2ae50b6 commit 5dd850d
Show file tree
Hide file tree
Showing 2 changed files with 49 additions and 1 deletion.
2 changes: 2 additions & 0 deletions test/Main.hs
Expand Up @@ -33,6 +33,8 @@ tests =
, TestLabel "ParamConv" . testParamConvFloat
, TestLabel "ParamConv" . testParamConvDateTime
, TestLabel "ParamConv" . testParamConvBools
, TestLabel "ParamConv" . testParamConvToRow
, TestLabel "ParamConv" . testParamConvFromRow
, TestLabel "Errors" . testErrorsColumns
, TestLabel "Errors" . testErrorsInvalidParams
, TestLabel "Errors" . testErrorsWithStatement
Expand Down
48 changes: 47 additions & 1 deletion test/ParamConv.hs
@@ -1,10 +1,13 @@
{-# LANGUAGE ScopedTypeVariables #-}

module ParamConv (
testParamConvNull
, testParamConvInt
, testParamConvFloat
, testParamConvBools
, testParamConvDateTime) where
, testParamConvDateTime
, testParamConvFromRow
, testParamConvToRow) where

import Data.Int
import Data.Time
Expand Down Expand Up @@ -93,3 +96,46 @@ testParamConvBools TestEnv{..} = TestCase $ do
assertEqual "bool" True r3
assertEqual "bool" False r4
assertEqual "bool" False r5

testParamConvFromRow :: TestEnv -> Test
testParamConvFromRow TestEnv{..} = TestCase $ do
[(1,2)] <- query_ conn "SELECT 1,2" :: IO [(Int,Int)]
[(1,2,3)] <- query_ conn "SELECT 1,2,3" :: IO [(Int,Int,Int)]
[(1,2,3,4)] <- query_ conn "SELECT 1,2,3,4" :: IO [(Int,Int,Int,Int)]
[(1,2,3,4,5)] <- query_ conn "SELECT 1,2,3,4,5" :: IO [(Int,Int,Int,Int,Int)]
[(1,2,3,4,5,6)] <- query_ conn "SELECT 1,2,3,4,5,6" :: IO [(Int,Int,Int,Int,Int,Int)]
[(1,2,3,4,5,6,7)] <- query_ conn "SELECT 1,2,3,4,5,6,7" :: IO [(Int,Int,Int,Int,Int,Int,Int)]
[(1,2,3,4,5,6,7,8)] <- query_ conn "SELECT 1,2,3,4,5,6,7,8" :: IO [(Int,Int,Int,Int,Int,Int,Int,Int)]
[(1,2,3,4,5,6,7,8,9)] <- query_ conn "SELECT 1,2,3,4,5,6,7,8,9" :: IO [(Int,Int,Int,Int,Int,Int,Int,Int,Int)]
[(1,2,3,4,5,6,7,8,9,10)] <- query_ conn "SELECT 1,2,3,4,5,6,7,8,9,10" :: IO [(Int,Int,Int,Int,Int,Int,Int,Int,Int,Int)]
[[1,2,3]] <- query_ conn "SELECT 1,2,3" :: IO [[Int]]
return ()

testParamConvToRow :: TestEnv -> Test
testParamConvToRow TestEnv{..} = TestCase $ do
[Only (s :: Int)] <- query conn "SELECT 13" ()
13 @=? s
[Only (s :: Int)] <- query conn "SELECT ?" (Only one)
1 @=? s
[Only (s :: Int)] <- query conn "SELECT ?+?" (one, two)
(1+2) @=? s
[Only (s :: Int)] <- query conn "SELECT ?+?+?" (one, two, three)
(1+2+3) @=? s
[Only (s :: Int)] <- query conn "SELECT ?+?+?+?" (one, two, three, 4 :: Int)
(1+2+3+4) @=? s
[Only (s :: Int)] <- query conn "SELECT ?+?+?+?+?" (one, two, three, 4 :: Int, 5 :: Int)
(1+2+3+4+5) @=? s
[Only (s :: Int)] <- query conn "SELECT ?+?+?+?+?+?" (one, two, three, 4 :: Int, 5 :: Int, 6 :: Int)
(1+2+3+4+5+6) @=? s
[Only (s :: Int)] <- query conn "SELECT ?+?+?+?+?+?+?"
(one, two, three, 4 :: Int, 5 :: Int, 6 :: Int, 7 :: Int)
(1+2+3+4+5+6+7) @=? s
[Only (s :: Int)] <- query conn "SELECT ?+?+?+?+?+?+?+?"
(one, two, three, 4 :: Int, 5 :: Int, 6 :: Int, 7 :: Int, 8 :: Int)
(1+2+3+4+5+6+7+8) @=? s
[Only (s :: Int)] <- query conn "SELECT ?+?+?+?+?+?+?+?+?"
(one, two, three, 4 :: Int, 5 :: Int, 6 :: Int, 7 :: Int, 8 :: Int, 9 :: Int)
(1+2+3+4+5+6+7+8+9) @=? s
[Only (s :: Int)] <- query conn "SELECT ?+?+?+?+?+?+?+?+?+?"
(one, two, three, 4 :: Int, 5 :: Int, 6 :: Int, 7 :: Int, 8 :: Int, 9 :: Int, 10 :: Int)
(1+2+3+4+5+6+7+8+9+10) @=? s

0 comments on commit 5dd850d

Please sign in to comment.