Removed now from typeclass and moved it to PostgreSQL. Testing for DB clock against machine clock

This commit is contained in:
Fintan Halpenny 2017-08-03 20:48:42 +01:00
parent 013dc19b15
commit 8eab68a8d3
5 changed files with 20 additions and 9 deletions

View File

@ -45,7 +45,7 @@ module Database.Esqueleto
, countRows, count, countDistinct
, not_, (==.), (>=.), (>.), (<=.), (<.), (!=.), (&&.), (||.)
, (+.), (-.), (/.), (*.)
, random_, now_, round_, ceiling_, floor_
, random_, round_, ceiling_, floor_
, min_, max_, sum_, avg_, castNum, castNumM
, coalesce, coalesceDefault
, lower_, like, ilike, (%), concat_, (++.), castString

View File

@ -53,7 +53,6 @@ import Text.Blaze.Html (Html)
import qualified Data.ByteString as B
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Data.Time.Clock (UTCTime)
-- | Finally tagless representation of @esqueleto@'s EDSL.
@ -353,7 +352,6 @@ class (Functor query, Applicative query, Monad query) =>
random_ :: (PersistField a, Num a) => expr (Value a)
now_ :: (PersistField a, a ~ UTCTime) => expr (Value a)
round_ :: (PersistField a, Num a, PersistField b, Num b) => expr (Value a) -> expr (Value b)
ceiling_ :: (PersistField a, Num a, PersistField b, Num b) => expr (Value a) -> expr (Value b)
floor_ :: (PersistField a, Num a, PersistField b, Num b) => expr (Value a) -> expr (Value b)

View File

@ -504,7 +504,6 @@ instance Esqueleto SqlQuery SqlExpr SqlBackend where
(*.) = unsafeSqlBinOp " * "
random_ = unsafeSqlValue "RANDOM()"
now_ = unsafeSqlValue "NOW()"
round_ = unsafeSqlFunction "ROUND"
ceiling_ = unsafeSqlFunction "CEILING"
floor_ = unsafeSqlFunction "FLOOR"

View File

@ -7,11 +7,12 @@ module Database.Esqueleto.PostgreSQL
( arrayAgg
, stringAgg
, chr
, now_
) where
import Database.Esqueleto.Internal.Language
import Database.Esqueleto.Internal.Sql
import Data.Time.Clock (UTCTime)
-- | (@array_agg@) Concatenate input values, including @NULL@s,
-- into an array.
@ -38,3 +39,6 @@ stringAgg expr delim = unsafeSqlFunction "string_agg" (expr, delim)
-- /Since: 2.2.11/
chr :: SqlString s => SqlExpr (Value Int) -> SqlExpr (Value s)
chr = unsafeSqlFunction "chr"
now_ :: SqlExpr (Value UTCTime)
now_ = unsafeSqlValue "NOW()"

View File

@ -51,7 +51,7 @@ import qualified Data.List as L
import qualified Data.Set as S
import qualified Data.Text.Lazy.Builder as TLB
import qualified Database.Esqueleto.Internal.Sql as EI
import Data.Time.Clock (UTCTime)
import Data.Time.Clock (getCurrentTime, diffUTCTime, NominalDiffTime)
-- Test schema
@ -645,10 +645,20 @@ main = do
#endif
return ()
it "works with now_" $
it "works with now" $
run $ do
_ <- select $ return (now_ :: SqlExpr (Value UTCTime))
return ()
nowDb <- select $ return EP.now_
nowUtc <- liftIO getCurrentTime
let halfSecond = realToFrac 0.5 :: NominalDiffTime
-- | Check the result is not null
liftIO $ nowDb `shouldSatisfy` (not . null)
-- | Unpack the now value
let (Value now: _) = nowDb
-- | Get the time diff and check it's less than half a second
liftIO $ diffUTCTime nowUtc now `shouldSatisfy` (< halfSecond)
it "works with round_" $
run $ do