Merge pull request #46 from FintanH/now

Now
This commit is contained in:
Chris Allen 2017-08-04 09:50:48 -05:00 committed by GitHub
commit 352fca204c
3 changed files with 30 additions and 4 deletions

View File

@ -74,6 +74,7 @@ library
, monad-logger
, conduit >= 1.1
, resourcet >= 1.1
, time >= 1.5.0.1 && <= 1.8.0.2
, blaze-html
hs-source-dirs: src/
if impl(ghc >= 8.0)
@ -101,6 +102,7 @@ test-suite test
, persistent-template >= 2.1
, monad-control
, monad-logger >= 0.3
, time >= 1.5.0.1 && <= 1.8.0.2
-- This library
, esqueleto

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,6 +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 (getCurrentTime, diffUTCTime, NominalDiffTime)
-- Test schema
@ -644,6 +645,23 @@ main = do
#endif
return ()
#if defined(WITH_POSTGRESQL)
it "works with now" $
run $ do
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)
#endif
it "works with round_" $
run $ do
ret <- select $ return $ round_ (val (16.2 :: Double))
@ -1140,9 +1158,8 @@ main = do
on $ lord ^. LordId ==. deed ^. DeedOwnerId
groupBy (lord ^. LordId)
return (lord ^. LordId, count $ deed ^. DeedId)
liftIO $ ret `shouldBe` [ (Value l3k, Value 7)
, (Value l1k, Value 3) ]
liftIO $ ret `shouldMatchList` [ (Value l3k, Value 7)
, (Value l1k, Value 3) ]
it "GROUP BY works with HAVING" $
run $ do
p1k <- insert p1
@ -1484,6 +1501,9 @@ cleanDB = do
delete $ from $ \(_ :: SqlExpr (Entity Follow)) -> return ()
delete $ from $ \(_ :: SqlExpr (Entity Person)) -> return ()
delete $ from $ \(_ :: SqlExpr (Entity Deed)) -> return ()
delete $ from $ \(_ :: SqlExpr (Entity Lord)) -> return ()
delete $ from $ \(_ :: SqlExpr (Entity CcList)) -> return ()
delete $ from $ \(_ :: SqlExpr (Entity ArticleTag)) -> return ()