Changelog, bifurcating random_

This commit is contained in:
Chris Allen 2018-02-27 18:19:46 -06:00
parent afdc7f792b
commit 391aa86464
10 changed files with 114 additions and 29 deletions

28
changelog.md Normal file
View File

@ -0,0 +1,28 @@
2.6.0
========
- @bitemyapp
- Reorganized dependencies, decided to break compatibility for Conduit 1.3, Persistent 2.8, and `unliftio`.
- Moved tests for `random()` into database-specific test suites.
- Deprecated Language `random_`, split it into database-specific modules.
- @parsonsmatt
- Added support for `PersistQueryRead`/`PersistQueryWrite`, enabling type-safe differentation of read and write capabilities.
- https://github.com/bitemyapp/esqueleto/pull/66
- @sestrella
- Added support for `arrayAggDistinct` and `arrayRemove`.
- https://github.com/bitemyapp/esqueleto/pull/65
- https://github.com/bitemyapp/esqueleto/pull/66
- @mheinzel
- Fixed JOIN syntax in the documentation https://github.com/bitemyapp/esqueleto/pull/60
- @illmade
- Added instructions for running database specific tests
- https://github.com/bitemyapp/esqueleto/pull/64
- @FintanH
- Removed CPP from the test suite, split the database-specific tests into their own respective modules.
- https://github.com/bitemyapp/esqueleto/pull/48
- Added support for PostgreSQL's `now()`
- https://github.com/bitemyapp/esqueleto/pull/46
- Added a comprehensive examples project to make practical application of Esqueleto easier.
- https://github.com/bitemyapp/esqueleto/pull/40
- @EdwardBetts
- Fixed a spelling error
- https://github.com/bitemyapp/esqueleto/pull/52

View File

@ -49,7 +49,9 @@ source-repository head
library
exposed-modules:
Database.Esqueleto
Database.Esqueleto.MySQL
Database.Esqueleto.PostgreSQL
Database.Esqueleto.SQLite
Database.Esqueleto.Internal.Language
Database.Esqueleto.Internal.Sql
other-modules:

View File

@ -589,6 +589,7 @@ class (Functor query, Applicative query, Monad query) =>
-- /Since: 2.4.3/
toBaseId :: ToBaseId ent => expr (Value (Key ent)) -> expr (Value (Key (BaseEnt ent)))
{-# DEPRECATED random_ "Since 2.6.0: `random_` is not uniform across all databases! Please use a specific one such as 'Database.Esqueleto.PostgreSQL.random_', 'Database.Esqueleto.MySQL.random_', or 'Database.Esqueleto.SQLite.random_'" #-}
-- Fixity declarations
infixl 9 ^.

View File

@ -297,7 +297,6 @@ useIdent :: IdentInfo -> Ident -> TLB.Builder
useIdent info (I ident) = fromDBName info $ DBName ident
----------------------------------------------------------------------
-- | An expression on the SQL backend.

View File

@ -0,0 +1,18 @@
{-# LANGUAGE OverloadedStrings #-}
-- | This module contain MySQL-specific functions.
--
-- /Since: 2.2.8/
module Database.Esqueleto.MySQL
( random_
) where
import Database.Esqueleto.Internal.Language hiding (random_)
import Database.Esqueleto.Internal.PersistentImport
import Database.Esqueleto.Internal.Sql
-- | (@random()@) Split out into database specific modules
-- because MySQL uses `rand()`.
--
-- /Since: 2.6.0/
random_ :: (PersistField a, Num a) => SqlExpr (Value a)
random_ = unsafeSqlValue "RAND()"

View File

@ -10,9 +10,11 @@ module Database.Esqueleto.PostgreSQL
, stringAgg
, chr
, now_
, random_
) where
import Database.Esqueleto.Internal.Language
import Database.Esqueleto.Internal.Language hiding (random_)
import Database.Esqueleto.Internal.PersistentImport
import Database.Esqueleto.Internal.Sql
import Data.Time.Clock (UTCTime)
@ -25,6 +27,13 @@ arrayAggDistinct = arrayAgg . distinct'
where
distinct' = unsafeSqlBinOp " " (unsafeSqlValue "DISTINCT")
-- | (@random()@) Split out into database specific modules
-- because MySQL uses `rand()`.
--
-- /Since: 2.6.0/
random_ :: (PersistField a, Num a) => SqlExpr (Value a)
random_ = unsafeSqlValue "RANDOM()"
-- | (@array_agg@) Concatenate input values, including @NULL@s,
-- into an array.
--

View File

@ -0,0 +1,18 @@
{-# LANGUAGE OverloadedStrings #-}
-- | This module contain SQLite-specific functions.
--
-- /Since: 2.2.8/
module Database.Esqueleto.SQLite
( random_
) where
import Database.Esqueleto.Internal.Language hiding (random_)
import Database.Esqueleto.Internal.PersistentImport
import Database.Esqueleto.Internal.Sql
-- | (@random()@) Split out into database specific modules
-- because MySQL uses `rand()`.
--
-- /Since: 2.6.0/
random_ :: (PersistField a, Num a) => SqlExpr (Value a)
random_ = unsafeSqlValue "RANDOM()"

View File

@ -19,6 +19,8 @@
module Common.Test
( tests
, testLocking
, testAscRandom
, testRandomMath
, migrateAll
, cleanDB
, RunDbMonad
@ -817,24 +819,6 @@ testSelectOrderBy run = do
return (b ^. BlogPostId)
liftIO $ ret `shouldBe` (Value <$> [b2k, b3k, b4k, b1k])
it "works with asc random_" $
run $ do
_p1e <- insert' p1
_p2e <- insert' p2
_p3e <- insert' p3
_p4e <- insert' p4
rets <-
fmap S.fromList $
replicateM 11 $
select $
from $ \p -> do
orderBy [asc (random_ :: SqlExpr (Value Double))]
return (p ^. PersonId :: SqlExpr (Value PersonId))
-- There are 2^4 = 16 possible orderings. The chance
-- of 11 random samplings returning the same ordering
-- is 1/2^40, so this test should pass almost everytime.
liftIO $ S.size rets `shouldSatisfy` (>2)
it "works on a composite primary key" $
run $ do
let ps = [Point 2 1 "", Point 1 2 ""]
@ -845,7 +829,26 @@ testSelectOrderBy run = do
return p'
liftIO $ map entityVal eps `shouldBe` reverse ps
testAscRandom :: SqlExpr (Value Double) -> Run -> Spec
testAscRandom rand' run =
describe "random_" $
it "asc random_ works" $
run $ do
_p1e <- insert' p1
_p2e <- insert' p2
_p3e <- insert' p3
_p4e <- insert' p4
rets <-
fmap S.fromList $
replicateM 11 $
select $
from $ \p -> do
orderBy [asc (rand' :: SqlExpr (Value Double))]
return (p ^. PersonId :: SqlExpr (Value PersonId))
-- There are 2^4 = 16 possible orderings. The chance
-- of 11 random samplings returning the same ordering
-- is 1/2^40, so this test should pass almost everytime.
liftIO $ S.size rets `shouldSatisfy` (>2)
testSelectDistinct :: Run -> Spec
testSelectDistinct run = do
@ -1195,10 +1198,8 @@ testInsertsBySelectReturnsCount run = do
testMathFunctions :: Run -> Spec
testMathFunctions run = do
describe "Math-related functions" $ do
testRandomMath :: Run -> Spec
testRandomMath run = describe "random_ math" $
it "rand returns result in random order" $
run $ do
replicateM_ 20 $ do
@ -1219,6 +1220,9 @@ testMathFunctions run = do
liftIO $ (ret1 == ret2) `shouldBe` False
testMathFunctions :: Run -> Spec
testMathFunctions run = do
describe "Math-related functions" $ do
it "castNum works for multiplying Int and Double" $
run $ do
mapM_ insert [Numbers 2 3.4, Numbers 7 1.1]

View File

@ -11,7 +11,8 @@ import Control.Monad (void)
import Control.Monad.IO.Class (MonadIO(liftIO))
import Control.Monad.Logger (runStderrLoggingT, runNoLoggingT)
import Control.Monad.Trans.Reader (ReaderT)
import Database.Esqueleto
import Database.Esqueleto hiding (random_)
import Database.Esqueleto.PostgreSQL (random_)
import Database.Persist.Postgresql (withPostgresqlConn)
import Data.Ord (comparing)
import Control.Arrow ((&&&))
@ -290,6 +291,8 @@ main = do
testLocking withConn
describe "PostgreSQL specific tests" $ do
testAscRandom random_ run
testRandomMath run
testSelectDistinctOn
testPostgresModule
testPostgresqlOneAscOneDesc
@ -314,7 +317,7 @@ run =
verbose :: Bool
verbose = True
verbose = False
migrateIt :: RunDbMonad m => SqlPersistT (R.ResourceT m) ()
migrateIt = do

View File

@ -13,7 +13,8 @@ import Control.Monad.Logger (runStderrLoggingT, runNoLoggingT)
import Control.Monad.Trans.Reader (ReaderT)
import Database.Persist.Sqlite (withSqliteConn)
import Database.Sqlite (SqliteException)
import Database.Esqueleto
import Database.Esqueleto hiding (random_)
import Database.Esqueleto.SQLite (random_)
import qualified Control.Monad.Trans.Resource as R
import Test.Hspec
@ -173,6 +174,8 @@ main = do
testLocking withConn
describe "SQLite specific tests" $ do
testAscRandom random_ run
testRandomMath run
testSqliteRandom
testSqliteSum
testSqliteTwoAscFields
@ -195,7 +198,7 @@ run =
verbose :: Bool
verbose = True
verbose = False
run_worker :: RunDbMonad m => SqlPersistT (R.ResourceT m) a -> m a