First version of a test suite.
This commit is contained in:
parent
fdf9985142
commit
f3e47321e2
@ -29,3 +29,24 @@ library
|
||||
, conduit
|
||||
hs-source-dirs: src/
|
||||
ghc-options: -Wall
|
||||
|
||||
test-suite test
|
||||
type: exitcode-stdio-1.0
|
||||
ghc-options: -Wall
|
||||
hs-source-dirs: test
|
||||
main-is: Test.hs
|
||||
build-depends:
|
||||
-- Library dependencies used on the tests. No need to
|
||||
-- specify versions since they'll use the same as above.
|
||||
base, persistent, transformers, conduit
|
||||
|
||||
-- Test-only dependencies
|
||||
, HUnit
|
||||
, QuickCheck
|
||||
, hspec == 1.3.*
|
||||
, hspec-expectations == 0.3.*
|
||||
, persistent-sqlite == 1.0.*
|
||||
, persistent-template == 1.0.*
|
||||
|
||||
-- This library
|
||||
, esqueleto
|
||||
|
||||
57
test/Test.hs
Normal file
57
test/Test.hs
Normal file
@ -0,0 +1,57 @@
|
||||
{-# LANGUAGE QuasiQuotes, TemplateHaskell, TypeFamilies, OverloadedStrings, GADTs, FlexibleContexts, EmptyDataDecls #-}
|
||||
|
||||
module Main (main) where
|
||||
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
import Database.Esqueleto
|
||||
import Database.Persist.Sqlite
|
||||
import Database.Persist.TH
|
||||
import Test.Hspec
|
||||
import Test.Hspec.Expectations
|
||||
import qualified Data.Conduit as C
|
||||
|
||||
|
||||
-- Test schema
|
||||
share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persist|
|
||||
Person
|
||||
name String
|
||||
age Int Maybe
|
||||
deriving Eq Show
|
||||
BlogPost
|
||||
title String
|
||||
authorId PersonId
|
||||
deriving Eq Show
|
||||
Follow
|
||||
follower PersonId
|
||||
followed PersonId
|
||||
deriving Eq Show
|
||||
|]
|
||||
|
||||
|
||||
runDB :: SqlPersist (C.ResourceT IO) a -> IO a
|
||||
runDB =
|
||||
C.runResourceT .
|
||||
withSqliteConn ":memory:" .
|
||||
runSqlConn .
|
||||
(runMigrationSilent migrateAll >>)
|
||||
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
let p1 = Person "John" (Just 36)
|
||||
p2 = Person "Rachel" Nothing
|
||||
p3 = Person "Mike" (Just 17)
|
||||
hspec $ do
|
||||
describe "select" $ do
|
||||
it "works for single value" $
|
||||
runDB $ do
|
||||
ret <- select $ return $ val (3 :: Int)
|
||||
liftIO $ ret `shouldBe` [ Single 3 ]
|
||||
describe "select/from" $ do
|
||||
it "works on a most simple example" $
|
||||
runDB $ do
|
||||
p1k <- insert p1
|
||||
ret <- select $
|
||||
from $ \person ->
|
||||
return person
|
||||
liftIO $ ret `shouldBe` [ Entity p1k p1 ]
|
||||
Loading…
Reference in New Issue
Block a user