[Haskell-cafe] [ANN] relational-record - relational-algebraic query building DSL

Kei Hibino ex8k.hibino at gmail.com
Fri Dec 19 16:50:16 UTC 2014


> On Fri, Dec 19, 2014 at 12:39:01PM +0900, Kei Hibino wrote:
>> From: Manuel Gómez <targen at gmail.com>
>> Subject: Re: [Haskell-cafe] [ANN] relational-record - relational-algebraic query building DSL
>> Date: Sun, 14 Dec 2014 12:22:25 -0430
>>
>> > On Sun, Dec 14, 2014 at 12:04 PM, Kei Hibino <ex8k.hibino at gmail.com> wrote:
>> >> I am happy to announce relational-record library and its project page.
>> >>
>> >> relational-record is domain specific language for type-safe SQL query building,
>> >> and database access API with compile time schema generators.
>> >
>> > Congratulations on the release!  It’s great to see more and more
>> > interesting abstractions for relational databases in the Haskell
>> > ecosystem.
>> >
>> > It looks like this project shares many goals with Tom Ellis’ excellent
>> > and recently released[1] Opaleye library.  How would you say your
>> > approach compares with Opaleye’s?
>> >
>> > [1]: <www.reddit.com/r/haskell/comments/2nxx7n/announcing_opaleye_sqlgenerating_embedded_domain/>
>>
>> Relational Record and Opaleye resembles in approach of building
>> not aggregated SQL query.
>>
>> Opaleye's method using arrow notation is very cool.
>
> Opaleye uses arrows only because it is hard to implement a sensible
> semantics otherwise.  See, for example, this bug report on HaskellDB which
> used a monad rather than an arrow
>
>     https://github.com/m4dc4p/haskelldb/issues/22
>
> Tom

In my -- Relational Record -- implementation,
this issue does not exist like exmaple code below.

Both not-finalized monad case (continuing table form building, justAgeOfFamilies0)
and finzlined monad (reuse defined table form, justAgeOfFamilies1) are no problem.

Key idea is separating out group-by accumulating state and aggregated key result.
Operator 'groupBy' accumulates aggregate key into monad stack,
and returns aggregated context-typed projection.

In aggregated relation, query result type and order-by specified key type are checked
to allow only aggregated context-typed projection.


> {-# LANGUAGE TemplateHaskell, MultiParamTypeClasses, FlexibleInstances #-}
>
> import Data.Int
>
> import Database.Relational.Query
> import Database.Relational.Query.TH
>
>
> $(defineTableDefault defaultConfig
>   "PUBLIC" "my_table"
>   [ ("person", [t| String |])
>   , ("family", [t| String |])
>   , ("age"   , [t| Int32 |])
>   ]
>   [] [0] (Just 0))
>
>
> agesOfFamiliesQ :: QueryAggregate (Projection Aggregated (String, Maybe Int32))
> agesOfFamiliesQ =  do
>   my <- query myTable
>   gFam <- groupBy $ my ! family'
>   return $ gFam >< sum' (my ! age')
>
> justAgeOfFamilies0 :: Relation () (Maybe Int32)
> justAgeOfFamilies0 =  aggregateRelation $ do
>   pair <- agesOfFamiliesQ
>   return $ pair ! snd'
>
> -- *Main> justAgeOfFamilies0
> -- SELECT ALL SUM (T0.age) AS f0 FROM PUBLIC.my_table T0 GROUP BY T0.family
>
> agesOfFamilies :: Relation () (String, Maybe Int32)
> agesOfFamilies =  aggregateRelation agesOfFamiliesQ
>
> justAgeOfFamilies1 :: Relation () (Maybe Int32)
> justAgeOfFamilies1 =  relation $ do
>   pair <- query agesOfFamilies
>   return $ pair ! snd'
>
> -- *Main> justAgeOfFamilies1
> -- SELECT ALL T1.f1 AS f0
> --   FROM (SELECT ALL T0.family AS f0, SUM (T0.age) AS f1
> --           FROM PUBLIC.my_table T0 GROUP BY T0.family) T1
>
> main :: IO ()
> main =  do
>   putStrLn "0"
>   print justAgeOfFamilies0
>   putStrLn "1"
>   print justAgeOfFamilies1

--
Kei Hibino
ex8k.hibino at gmail.com


More information about the Haskell-Cafe mailing list