Cleaning up code

This commit is contained in:
Fintan Halpenny 2017-08-09 22:49:18 +01:00
parent 1262c3fef9
commit 6b0028ed69
4 changed files with 60 additions and 43 deletions

View File

@ -1414,7 +1414,7 @@ tests run = do
testCase run
testCountingRows run
----------------------------------------------------------------------
-------------------------------------------------------------------------------
insert' :: ( Functor m
@ -1463,42 +1463,3 @@ cleanDB = do
delete $ from $ \(_ :: SqlExpr (Entity Point)) -> return ()
delete $ from $ \(_ :: SqlExpr (Entity Numbers)) -> return ()
-- run, runSilent, runVerbose :: Run a
-- runSilent act = runNoLoggingT $ run_worker act
-- runVerbose act = runStderrLoggingT $ run_worker act
-- run =
-- if verbose
-- then runVerbose
-- else runSilent
--
--
-- verbose :: Bool
-- verbose = True
--
--
-- run_worker :: RunDbMonad m => SqlPersistT (R.ResourceT m) a -> m a
-- run_worker act = withConn $ runSqlConn (migrateIt >> act)
--
--
-- migrateIt :: RunDbMonad m => SqlPersistT (R.ResourceT m) ()
-- migrateIt = do
-- void $ runMigrationSilent migrateAll
-- #if defined (WITH_POSTGRESQL) || defined (WITH_MYSQL)
-- cleanDB
-- #endif
--
--
-- withConn :: RunDbMonad m => (SqlBackend -> R.ResourceT m a) -> m a
-- withConn =
-- R.runResourceT .
-- #if defined (WITH_MYSQL)
-- withMySQLConn defaultConnectInfo
-- { connectHost = "localhost"
-- , connectUser = "esqutest"
-- , connectPassword = "esqutest"
-- , connectDatabase = "esqutest"
-- }
-- #else
-- withSqliteConn ":memory:"
-- #endif

View File

@ -138,6 +138,9 @@ main = do
hspec $ do
tests run
describe "Test MySQL locking" $ do
testLocking withConn
describe "MySQL specific tests" $ do
testMysqlRandom
testMysqlSum
@ -149,6 +152,7 @@ main = do
-------------------------------------------------------------------------------
run, runSilent, runVerbose :: Run
runSilent act = runNoLoggingT $ run_worker act
runVerbose act = runStderrLoggingT $ run_worker act

View File

@ -32,6 +32,8 @@ import Data.Time.Clock (getCurrentTime, diffUTCTime)
import Common.Test
-------------------------------------------------------------------------------
testPostgresqlCoalesce :: Spec
testPostgresqlCoalesce = do
@ -44,6 +46,9 @@ testPostgresqlCoalesce = do
return ()
-------------------------------------------------------------------------------
testPostgresqlTextFunction :: Spec
testPostgresqlTextFunction = do
it "ilike, (%) and (++.) work on a simple example on PostgreSQL" $
@ -60,6 +65,9 @@ testPostgresqlTextFunction = do
nameContains "JOHN" [p1e]
-------------------------------------------------------------------------------
testPostgresqlUpdate :: Spec
testPostgresqlUpdate = do
it "works on a simple example" $
@ -87,6 +95,9 @@ testPostgresqlUpdate = do
, Entity p3k p3 ]
-------------------------------------------------------------------------------
testPostgresqlRandom :: Spec
testPostgresqlRandom = do
it "works with random_" $
@ -95,6 +106,9 @@ testPostgresqlRandom = do
return ()
-------------------------------------------------------------------------------
testPostgresqlSum :: Spec
testPostgresqlSum = do
it "works with sum_" $
@ -109,6 +123,9 @@ testPostgresqlSum = do
liftIO $ ret `shouldBe` [ Value $ Just (36 + 17 + 17 :: Rational ) ]
-------------------------------------------------------------------------------
testPostgresqlTwoAscFields :: Spec
testPostgresqlTwoAscFields = do
it "works with two ASC fields (one call)" $
@ -125,6 +142,9 @@ testPostgresqlTwoAscFields = do
liftIO $ ret `shouldBe` [ p4e, p3e, p1e , p2e ]
-------------------------------------------------------------------------------
testPostgresqlOneAscOneDesc :: Spec
testPostgresqlOneAscOneDesc = do
it "works with one ASC and one DESC field (two calls)" $
@ -141,7 +161,7 @@ testPostgresqlOneAscOneDesc = do
liftIO $ ret `shouldBe` [ p2e, p1e, p4e, p3e ]
----------------------------------------------------------------------
-------------------------------------------------------------------------------
testSelectDistinctOn :: Spec
@ -192,7 +212,7 @@ testSelectDistinctOn = do
distinctOnOrderBy [asc (bp ^. BlogPostAuthorId), asc (bp ^. BlogPostTitle)]
----------------------------------------------------------------------
-------------------------------------------------------------------------------
testPostgresModule :: Spec
@ -237,7 +257,7 @@ testPostgresModule = do
liftIO $ diffUTCTime nowUtc now `shouldSatisfy` (< halfSecond)
----------------------------------------------------------------------
-------------------------------------------------------------------------------
main :: IO ()
@ -259,6 +279,10 @@ main = do
testPostgresqlTextFunction
testPostgresqlCoalesce
-------------------------------------------------------------------------------
run, runSilent, runVerbose :: Run
runSilent act = runNoLoggingT $ run_worker act
runVerbose act = runStderrLoggingT $ run_worker act

View File

@ -17,6 +17,8 @@ import Test.Hspec
import Common.Test
-------------------------------------------------------------------------------
testSqliteRandom :: Spec
testSqliteRandom = do
@ -25,6 +27,10 @@ testSqliteRandom = do
_ <- select $ return (random_ :: SqlExpr (Value Int))
return ()
-------------------------------------------------------------------------------
testSqliteSum :: Spec
testSqliteSum = do
it "works with sum_" $
@ -38,6 +44,10 @@ testSqliteSum = do
return $ joinV $ sum_ (p ^. PersonAge)
liftIO $ ret `shouldBe` [ Value $ Just (36 + 17 + 17 :: Int) ]
-------------------------------------------------------------------------------
testSqliteTwoAscFields :: Spec
testSqliteTwoAscFields = do
it "works with two ASC fields (one call)" $
@ -53,6 +63,10 @@ testSqliteTwoAscFields = do
-- in SQLite and MySQL, its the reverse
liftIO $ ret `shouldBe` [ p2e, p4e, p3e, p1e ]
-------------------------------------------------------------------------------
testSqliteOneAscOneDesc :: Spec
testSqliteOneAscOneDesc = do
it "works with one ASC and one DESC field (two calls)" $
@ -69,6 +83,9 @@ testSqliteOneAscOneDesc = do
liftIO $ ret `shouldBe` [ p1e, p4e, p3e, p2e ]
-------------------------------------------------------------------------------
testSqliteCoalesce :: Spec
testSqliteCoalesce = do
it "throws an exception on SQLite with <2 arguments" $
@ -78,6 +95,9 @@ testSqliteCoalesce = do
`shouldThrow` (\(_ :: SqliteException) -> True)
-------------------------------------------------------------------------------
testSqliteUpdate :: Spec
testSqliteUpdate = do
it "works on a simple example" $
@ -103,6 +123,10 @@ testSqliteUpdate = do
, Entity p1k (Person anon (Just 73) Nothing 1)
, Entity p3k p3 ]
-------------------------------------------------------------------------------
main :: IO ()
main = do
hspec $ do
@ -119,6 +143,10 @@ main = do
testSqliteCoalesce
testSqliteUpdate
-------------------------------------------------------------------------------
run, runSilent, runVerbose :: Run
runSilent act = runNoLoggingT $ run_worker act
runVerbose act = runStderrLoggingT $ run_worker act