haskell-opaleye icon indicating copy to clipboard operation
haskell-opaleye copied to clipboard

What is the replacement for the deprecated functions, arrangeInsertManySql and arrangeUpdateSql

Open cscalfani opened this issue 6 years ago • 11 comments

I'm using these functions for logging the SQL that is going to be sent to the DB.

I couldn't find any functions for doing this that were not deprecated.

Appreciate the help.

cscalfani avatar Dec 08 '18 04:12 cscalfani

Hello @cscalfani. We need functions similar to runInsert_, called say, arrangeInsert, etc., that call the arrange... functions instead of the run... functions. Do you feel like implementing that?

tomjaguarpaw avatar Dec 08 '18 07:12 tomjaguarpaw

Two issues. First, it will take me some time to get familiar with the codebase. I've never spent much time doing so and therefore don't feel very confident. Second, I don't want to commit to doing this until the project I'm currently working on is complete (about 3 months from now). If after that time, I'm available and this work has not been done, I wouldn't mind spending time looking into it.

cscalfani avatar Dec 08 '18 16:12 cscalfani

This should be very easy, even for a new user of Opaleye. There need to be three functions

showSqlUpdate_ :: -> Update haskells -> String

showSqlInsert_ :: -> Insert haskells -> String

showSqlDelete_ :: -> Delete haskells -> String

They would be implemented in almost exactly the same way as the run..._ functions but using arrange... rather than run... in the implementation.

tomjaguarpaw avatar Dec 09 '18 09:12 tomjaguarpaw

@cscalfani Did you end up figuring out a way to render the Insert, Update and Deletes?

I'm trying to use Opaleye queries through a different connection lib than postgresql-simple so I need to explicitly, and hopefully with good performance, render each query (ByteString) before sending them over to my Postgres client lib.

tuomohopia avatar Mar 19 '20 00:03 tuomohopia

So I turned my brain off last night and just manually extracted the functionality out of the existing/deprecating functions of Opaleye for showSqlUpdate_. For the record, it looks like this

{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts          #-}
{-# LANGUAGE FlexibleInstances         #-}
{-# LANGUAGE GADTs                     #-}
{-# LANGUAGE MultiParamTypeClasses     #-}

module OpaleyeHelpers
  ( showSqlUpdate_
  )
where

import           Data.ByteString.Lazy.UTF8     as BLU

import qualified Opaleye                       as O
import qualified Opaleye.Internal.Sql          as Sql
import qualified Opaleye.Internal.Print        as Print
import qualified Opaleye.RunQuery              as RQ
import qualified Opaleye.Internal.RunQuery     as IRQ
import qualified Opaleye.Table                 as T
import qualified Opaleye.Internal.Table        as TI
import           Opaleye.Internal.Column        ( Column(Column) )
import           Opaleye.Internal.Helpers       ( (.:.) , (.::.) )
import qualified Opaleye.Internal.Manipulation as MI
import qualified Opaleye.Internal.PrimQuery    as PQ
import qualified Opaleye.Internal.Unpackspec   as U
import           Opaleye.SqlTypes               ( SqlBool )
import qualified Opaleye.Internal.HaskellDB.Sql as HSql
import qualified Opaleye.Internal.HaskellDB.Sql.Print as HPrint
import qualified Opaleye.Internal.HaskellDB.Sql.Default as SD
import qualified Opaleye.Internal.HaskellDB.Sql.Generate as SG

showSqlUpdate_ :: O.Update haskells -> BLU.ByteString
showSqlUpdate_ (O.Update table_ updateWith_ where_ returning_) = 
 render table_ updateWith_ where_
 where
  render = case returning_ of
    MI.Count -> renderUpdate
    MI.ReturningExplicit qr f ->
      \t u w -> runUpdateReturningExplicit qr t u w f

renderUpdate
  :: O.Table columnsW columnsR
  -> (columnsR -> columnsW)
  -> (columnsR -> Column SqlBool)
  -> BLU.ByteString
renderUpdate = BLU.fromString .:. arrangeUpdateSql

arrangeUpdateSql
  :: O.Table columnsW columnsR
  -> (columnsR -> columnsW)
  -> (columnsR -> Column SqlBool)
  -> String
arrangeUpdateSql = show . HPrint.ppUpdate .:. arrangeUpdate

arrangeUpdate
  :: O.Table columnsW columnsR
  -> (columnsR -> columnsW)
  -> (columnsR -> Column SqlBool)
  -> HSql.SqlUpdate
arrangeUpdate t update cond = 
  SG.sqlUpdate SD.defaultSqlGenerator (PQ.tiToSqlTable (TI.tableIdentifier t)) [condExpr]
   (update' tableCols)
 where
  TI.TableProperties writer (TI.View tableCols) = TI.tableColumns t
  update'         = map (\(x, y) -> (y, x)) . TI.runWriter writer . update
  Column condExpr = cond tableCols

runUpdateReturningExplicit
  :: RQ.QueryRunner columnsReturned haskells
  -> T.Table columnsW columnsR
  -> (columnsR -> columnsW)
  -> (columnsR -> Column SqlBool)
  -> (columnsR -> columnsReturned)
  -> BLU.ByteString
runUpdateReturningExplicit qr = arrangeUpdateReturningSql u
  where IRQ.QueryRunner u _ _ = qr

arrangeUpdateReturningSql
  :: U.Unpackspec columnsReturned ignored
  -> T.Table columnsW columnsR
  -> (columnsR -> columnsW)
  -> (columnsR -> Column SqlBool)
  -> (columnsR -> columnsReturned)
  -> BLU.ByteString
arrangeUpdateReturningSql =
  BLU.fromString . show . Print.ppUpdateReturning .::. arrangeUpdateReturning

arrangeUpdateReturning
  :: U.Unpackspec columnsReturned ignored
  -> T.Table columnsW columnsR
  -> (columnsR -> columnsW)
  -> (columnsR -> Column SqlBool)
  -> (columnsR -> columnsReturned)
  -> Sql.Returning HSql.SqlUpdate
arrangeUpdateReturning unpackspec t updatef cond returningf =
  Sql.Returning update returningSEs
 where
  update           = arrangeUpdate t updatef cond
  TI.View columnsR = TI.tableColumnsView (TI.tableColumns t)
  returningPEs     = U.collectPEs unpackspec (returningf columnsR)
  returningSEs     = Sql.ensureColumnsGen id (map Sql.sqlExpr returningPEs)

It appears to be working.

tuomohopia avatar Mar 19 '20 11:03 tuomohopia

Ideally though, we would do better with a specialized type class or even an instance of Show for all the relevant types, that would combine the functionality of arrange* and showSql. Logging of queries is a feature of obvious utility, and we already have all the pieces in place.

@tomjaguarpaw What do you think? Should it be instance Show, class ShowSql, or a collection of monomorphic functions like showSqlSelect, showSqlInsert and so on? I can write it up if you have time to review and merge.

See also #312 and #311.

kindaro avatar May 14 '20 18:05 kindaro

We already have Opaleye.Sql.showSql. I suggest adding showInsert, showUpdate and showDelete there.

tomjaguarpaw avatar May 14 '20 19:05 tomjaguarpaw

My view is that showSql would not be a great name in this context — it suggests more generality than actually provided. The thing should be called showSelect instead to be in line with the other three. A backwards compatible way to fix this would be to make showSql a method of a type class that includes all four SQL types. I am not sure what your philosophy as regards class based polymorphism is. The other way is to copy showSql to showSelect and eventually deprecate the former.

In the meanwhile, I hope to make a pull request before the end of May.

kindaro avatar May 14 '20 20:05 kindaro

 The other way is to copy showSql to showSelect and eventually deprecate the former.

This would be my preferred approach. Future work that I have got lined up with probably change the type, too, to no longer return a Maybe, so if we introduce the latter in the meantime, it should be called showSelectMaybe.

tomjaguarpaw avatar May 14 '20 21:05 tomjaguarpaw

I am sorry, I could not find the time to get this done yet. It is not entirely trivial — seems that some refactoring is required to ensure that exactly the same string is obtained as would be sent to PostgreSQL. I still hope to get this done, but I cannot say when.

kindaro avatar Jun 09 '20 18:06 kindaro

That's OK. Thanks for letting me know, and if you need any more assistance you're welcome to post more details.

tomjaguarpaw avatar Jun 09 '20 19:06 tomjaguarpaw