Skip to content

Commit

Permalink
Merge pull request #1428 from simplex-chat/ep/postgres-compat
Browse files Browse the repository at this point in the history
agent: restore methods for backwards compatibility with simplex-chat
  • Loading branch information
epoberezkin authored Dec 28, 2024
2 parents 69fb9a9 + cfde593 commit 3cf9dac
Showing 1 changed file with 13 additions and 1 deletion.
14 changes: 13 additions & 1 deletion src/Simplex/Messaging/Agent/Store/SQLite/DB.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,10 @@ module Simplex.Messaging.Agent.Store.SQLite.DB
execute,
execute_,
executeMany,
executeNamed,
query,
query_,
queryNamed,
)
where

Expand All @@ -31,7 +33,7 @@ import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
import Data.Text (Text)
import Data.Time (diffUTCTime, getCurrentTime)
import Database.SQLite.Simple (FromRow, Query, ToRow)
import Database.SQLite.Simple (FromRow, NamedParam, Query, ToRow)
import qualified Database.SQLite.Simple as SQL
import Database.SQLite.Simple.FromField (FromField (..))
import Database.SQLite.Simple.ToField (ToField (..))
Expand Down Expand Up @@ -103,6 +105,11 @@ execute_ :: Connection -> Query -> IO ()
execute_ Connection {conn, slow} sql = timeIt slow sql $ SQL.execute_ conn sql
{-# INLINE execute_ #-}

-- TODO [postgres] remove
executeNamed :: Connection -> Query -> [NamedParam] -> IO ()
executeNamed Connection {conn, slow} sql = timeIt slow sql . SQL.executeNamed conn sql
{-# INLINE executeNamed #-}

executeMany :: ToRow q => Connection -> Query -> [q] -> IO ()
executeMany Connection {conn, slow} sql = timeIt slow sql . SQL.executeMany conn sql
{-# INLINE executeMany #-}
Expand All @@ -115,4 +122,9 @@ query_ :: FromRow r => Connection -> Query -> IO [r]
query_ Connection {conn, slow} sql = timeIt slow sql $ SQL.query_ conn sql
{-# INLINE query_ #-}

-- TODO [postgres] remove
queryNamed :: FromRow r => Connection -> Query -> [NamedParam] -> IO [r]
queryNamed Connection {conn, slow} sql = timeIt slow sql . SQL.queryNamed conn sql
{-# INLINE queryNamed #-}

$(J.deriveJSON defaultJSON ''SlowQueryStats)

0 comments on commit 3cf9dac

Please sign in to comment.