Add array_agg function, new PostgreSQL module.

This commit is contained in:
Felipe Lessa 2015-07-15 12:28:26 -03:00
parent 9552180629
commit 6c63f2c5ac
4 changed files with 59 additions and 1 deletions

View File

@ -1,5 +1,5 @@
name: esqueleto
version: 2.2.7
version: 2.2.8
synopsis: Type-safe EDSL for SQL queries on persistent backends.
homepage: https://github.com/prowdsponsor/esqueleto
license: BSD3
@ -57,6 +57,7 @@ Flag mysql
library
exposed-modules:
Database.Esqueleto
Database.Esqueleto.PostgreSQL
Database.Esqueleto.Internal.Language
Database.Esqueleto.Internal.Sql
other-modules:

View File

@ -87,6 +87,9 @@ module Database.Esqueleto
, (<#)
, (<&>)
-- * RDBMS-specific modules
-- $rdbmsSpecificModules
-- * Helpers
, valkey
, valJ
@ -380,6 +383,22 @@ import qualified Database.Persist
----------------------------------------------------------------------
-- $rdbmsSpecificModules
--
-- There are many differences between SQL syntax and functions
-- supported by different RDBMSs. Since version 2.2.8,
-- @esqueleto@ includes modules containing functions that are
-- specific to a given RDBMS.
--
-- * PostgreSQL: "Database.Esqueleto.PostgreSQL".
--
-- In order to use these functions, you need to explicitly import
-- their corresponding modules, they're not re-exported here.
----------------------------------------------------------------------
-- | @valkey i = 'val' . 'toSqlKey'@
-- (<https://github.com/prowdsponsor/esqueleto/issues/9>).
valkey :: (Esqueleto query expr backend, ToBackendKey SqlBackend entity, PersistField (Key entity)) =>

View File

@ -0,0 +1,19 @@
{-# LANGUAGE OverloadedStrings
#-}
-- | This module contain PostgreSQL-specific functions.
--
-- /Since: 2.2.8/
module Database.Esqueleto.PostgreSQL
( arrayAgg
) where
import Database.Esqueleto.Internal.Language
import Database.Esqueleto.Internal.Sql
-- | (@array_agg@) Concatenate input values, including @NULL@s,
-- into an array.
--
-- /Since: 2.2.8/
arrayAgg :: SqlExpr (Value a) -> SqlExpr (Value [a])
arrayAgg = unsafeSqlFunction "array_agg"

View File

@ -53,6 +53,7 @@ import qualified Control.Monad.Trans.Resource as R
import qualified Data.List as L
import qualified Data.Set as S
import qualified Data.Text.Lazy.Builder as TLB
import qualified Database.Esqueleto.PostgreSQL as EP
import qualified Database.Esqueleto.Internal.Sql as EI
@ -1313,6 +1314,24 @@ main = do
it "looks sane for ForShare" $ sanityCheck ForShare "FOR SHARE"
it "looks sane for LockInShareMode" $ sanityCheck LockInShareMode "LOCK IN SHARE MODE"
describe "PostgreSQL module" $ do
it "should be tested on the PostgreSQL database" $
#if !defined(WITH_POSTGRESQL)
pendingWith "test suite not running under PostgreSQL, skipping"
#else
(return () :: IO ())
it "arrayAgg looks sane" $
run $ do
let people = [p1, p2, p3, p4, p5]
mapM_ insert people
[Value ret] <-
select $
from $ \p -> do
return (EP.arrayAgg (p ^. PersonName))
liftIO $ L.sort ret `shouldBe` L.sort (map personName people)
#endif
----------------------------------------------------------------------