Skip to content

Commit

Permalink
Added logging of database query times.
Browse files Browse the repository at this point in the history
  • Loading branch information
zacwood9 committed Feb 10, 2021
1 parent a36e807 commit 9371aa3
Showing 1 changed file with 14 additions and 8 deletions.
22 changes: 14 additions & 8 deletions IHP/ModelSupport.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ import Data.String.Conversions (cs ,ConvertibleStrings)
import Data.Time.Clock
import Data.Time.LocalTime
import Data.Time.Calendar
import Data.Time.Format
import Unsafe.Coerce
import Data.UUID
import qualified Database.PostgreSQL.Simple as PG
Expand Down Expand Up @@ -300,8 +301,12 @@ instance Default (PrimaryKey model) => Default (Id' model) where
-- Take a look at "IHP.QueryBuilder" for a typesafe approach on building simple queries.
sqlQuery :: (?modelContext :: ModelContext, PG.ToRow q, PG.FromRow r, Show q) => Query -> q -> IO [r]
sqlQuery theQuery theParameters = do
logQuery theQuery theParameters
withDatabaseConnection \connection -> PG.query connection theQuery theParameters
start <- getCurrentTime
result <- withDatabaseConnection \connection -> PG.query connection theQuery theParameters
end <- getCurrentTime
let theTime = end `diffUTCTime` start
logQuery theQuery theParameters theTime
pure result
{-# INLINABLE sqlQuery #-}


Expand All @@ -312,7 +317,7 @@ sqlQuery theQuery theParameters = do
-- > sqlExec "CREATE TABLE users ()" ()
sqlExec :: (?modelContext :: ModelContext, PG.ToRow q, Show q) => Query -> q -> IO Int64
sqlExec theQuery theParameters = do
logQuery theQuery theParameters
-- logQuery theQuery theParameters
withDatabaseConnection \connection -> PG.execute connection theQuery theParameters
{-# INLINABLE sqlExec #-}

Expand Down Expand Up @@ -357,12 +362,13 @@ tableNameByteString :: forall model. (KnownSymbol (GetTableName model)) => ByteS
tableNameByteString = symbolToByteString @(GetTableName model)
{-# INLINE tableNameByteString #-}

logQuery :: (?modelContext :: ModelContext, Show query, Show parameters) => query -> parameters -> IO ()
logQuery query parameters = do
let logMessage = (query, parameters)
|> tshow
logQuery :: (?modelContext :: ModelContext, Show query, Show parameters) => query -> parameters -> NominalDiffTime -> IO ()
logQuery query parameters time = do
let ?context = ?modelContext
Log.debug logMessage
-- NominalTimeDiff is represented as seconds, and doesn't provide a FormatTime option for printing in ms.
-- To get around that we convert to and from a rational so we can format as desired.
let queryTimeInMs = (time * 1000) |> toRational |> fromRational @Double
Log.debug ("Query (" <> tshow queryTimeInMs <> "ms): " <> tshow query <> " " <> tshow parameters)
{-# INLINABLE logQuery #-}

-- | Runs a @DELETE@ query for a record.
Expand Down

0 comments on commit 9371aa3

Please sign in to comment.