Skip to content

Commit

Permalink
Added SQLData FromField
Browse files Browse the repository at this point in the history
+ tests
  • Loading branch information
LindaOrtega authored and nurpax committed Jun 12, 2018
1 parent dcd9a16 commit 9e1382e
Show file tree
Hide file tree
Showing 3 changed files with 30 additions and 1 deletion.
3 changes: 3 additions & 0 deletions Database/SQLite/Simple/FromField.hs
Expand Up @@ -195,6 +195,9 @@ instance FromField Day where

fromField f = returnError ConversionFailed f "expecting SQLText column type"

instance FromField SQLData where
fromField f = Ok (fieldData f)

fieldTypename :: Field -> String
fieldTypename = B.unpack . gettypename . result

Expand Down
1 change: 1 addition & 0 deletions test/Main.hs
Expand Up @@ -54,6 +54,7 @@ tests =
, TestLabel "Utf8" . testUtf8Simplest
, TestLabel "Utf8" . testBlobs
, TestLabel "Instances" . testUserFromField
, TestLabel "Instances" . testSQLDataFromField
, TestLabel "Fold" . testFolds
, TestLabel "Statement" . testBind
, TestLabel "Statement" . testDoubleBind
Expand Down
27 changes: 26 additions & 1 deletion test/UserInstances.hs
@@ -1,8 +1,12 @@
{-# LANGUAGE DeriveDataTypeable #-}

module UserInstances (testUserFromField) where
module UserInstances (
testUserFromField
,testSQLDataFromField
) where

import Common
import Data.Int (Int64)
import Data.Typeable (Typeable)
import qualified Data.Text as T
import Database.SQLite.Simple.FromField
Expand Down Expand Up @@ -31,3 +35,24 @@ testUserFromField TestEnv{..} = TestCase $ do
execute conn "INSERT INTO fromfield (t) VALUES (?)" (Only (MyType "test2"))
[Only r] <- query_ conn "SELECT t FROM fromfield" :: IO [(Only String)]
"toField test2" @=? r

testSQLDataFromField :: TestEnv -> Test
testSQLDataFromField TestEnv{..} = TestCase $ do
execute_ conn "CREATE TABLE sqldatafromfield (t TEXT, i INT, b BOOLEAN, f FLOAT)"
execute conn "INSERT INTO sqldatafromfield (t,i,b,f) VALUES (?,?,?,?)" (("test string" :: T.Text,
1 :: Int64,
True :: Bool,
1.11 :: Double))
execute conn "INSERT INTO sqldatafromfield (t,i,b) VALUES (?,?,?)" (("test string2" :: T.Text,
2 :: Int64,
False :: Bool))
r <- query_ conn "SELECT * FROM sqldatafromfield" :: IO [[SQLData]]
let testData = [[SQLText "test string",
SQLInteger 1,
SQLInteger 1,
SQLFloat 1.11],
[SQLText "test string2",
SQLInteger 2,
SQLInteger 0,
SQLNull]]
testData @=? r

0 comments on commit 9e1382e

Please sign in to comment.