effectful-opaleye
Safe HaskellNone
LanguageHaskell2010

Effectful.Opaleye.Count

Description

Thanks to our dynamic Opaleye effect, we can write an alternative interpreter which, as well as performing SQL operations as before, will also keep a tally of the number of SQL operations (SELECTs, INSERTs etc) that have been performed. This is really useful for debugging.

The intended use-case is a sort of benchmark that runs several Opaleye operations for different "sizes", counts the SQL operations, and prints the tallies to the console. This lets us detect if some datbase operations are ineffecient.

For example, suppose our model has users with UserIds; those users an have multiple Transactions, which are composed of multiple SubTransactions etc. To insert a group of new users, we would need to insert the users, insert the transactions, and insert the subtransactions. Ideally, the number of INSERTs should not depend on the number of Users or the number or size of their Transactions. We would expect the number of SELECTs to remain basically constant (O(1)), while the execution time might grow linearly (O(u * t * s)).

A very naive implementation might be:

insertUsersNaive :: (Opaleye :> es) => [User] -> Eff es ()
insertUsersNaive users = for_ users $ user -> do
  insertUserFlat user
  for (transactions user) $ transaction -> do
    insertTransactionFlat transaction
    for (subTransactions transaction) $ subTransaction -> do
      insertSubTransactionFlat subTransaction

However, if we ran a "benchmark" that looked something like this:

u1, u5, u10, u50 :: [User]
u1 = [User {transactions = [Transaction [SubTransaction]]}] -- one user, one transaction, one sub-transaction
u5 = ...  -- five users, each with five transactions, each with 5 sub-transactions

benchmark :: (Opaleye :> es, State SQLOperationCounts :> es, IOE :> es) => Eff es ()
benchmark = for_ [(1, u1), (5, u5), (10, u10), (50, u50)] $ (n, users) -> do
  (counts, ()) <- withCounts $ insertUsersNaive users
  liftIO . putStrLn $ "Counts at n=" <> show n <> ": " <> renderCountsBrief counts

main :: IO ()
main = runEff . runWithConnectInfo connInfo . evalState @SQLOperationCounts mempty . runOpaleyeWithConnectionCounting $ benchmark
  where
    connInfo = ...

We will probably see something like:

Counts at n=1: INSERT: 3
Counts at n=5: INSERT: 155
Counts at n=10: INSERT: 1110
Counts at n=50: INSERT: 127550

This is obviously going to have a severe performance impact. Rearranging our implementatino of insertUsers:

insertUsersBetter :: (Opaleye :> es) => [User] -> Eff es ()
insertUsersBetter users = do
  let transactions_ = concatMap transactions users
      subTransactions_ = concatMap subTransactions transactions_
  insertUsersFlat users
  insertTransactionsFlat transactions_
  insertSubTransactionsFlat subTransactions_

As long as insertTransactionsFlat etc are smart enough to only do one runInsert, then we should now get:

Counts at n=1: INSERT: 3
Counts at n=5: INSERT: 3
Counts at n=10: INSERT: 3
Counts at n=50: INSERT: 3

Note that we used renderCountsBrief for simplicity. If we wanted to debug in more detail, we could have used renderCounts instead:

Counts at n=1: INSERT: user: 1
                       transaction: 1
                       sub_transaction: 1
Counts at n=5: INSERT: user: 5
                       transaction: 25
                       sub_transaction: 125
Counts at n=10: INSERT: user: 10
                        transaction: 100
                        sub_transaction: 1000
Counts at n=50: INSERT: user: 50
                        transaction: 2500
                        sub_transaction: 125000
Synopsis

Counting SQL operations

data SQLOperationCounts Source #

This tracks the number of SQL operations that have been performed in the Opaleye effect, along with which table it was performed on (where possible).

INSERT, DELETE and UPDATE operations act on one table only, so we can tally the number of each that are performed on each table (indexed by a QualifiedIdentifier). SELECT operations can act on multiple tables, so we just track the total number of selects.

If required, SQLOperationCounts can be constructed using Monoid and combined using Semigroup.

We use non-negative Naturals as a tally since a negative number of operations makes no sense.

Instances

Instances details
Monoid SQLOperationCounts Source # 
Instance details

Defined in Effectful.Opaleye.Count

Semigroup SQLOperationCounts Source # 
Instance details

Defined in Effectful.Opaleye.Count

Generic SQLOperationCounts Source # 
Instance details

Defined in Effectful.Opaleye.Count

Associated Types

type Rep SQLOperationCounts 
Instance details

Defined in Effectful.Opaleye.Count

Show SQLOperationCounts Source # 
Instance details

Defined in Effectful.Opaleye.Count

Eq SQLOperationCounts Source # 
Instance details

Defined in Effectful.Opaleye.Count

Pretty SQLOperationCounts Source # 
Instance details

Defined in Effectful.Opaleye.Count

type Rep SQLOperationCounts Source # 
Instance details

Defined in Effectful.Opaleye.Count

opaleyeAddCounting :: forall a (es :: [Effect]). (HasCallStack, State SQLOperationCounts :> es) => Eff (Opaleye ': es) a -> Eff (Opaleye ': es) a Source #

Add counting of SQL operations to the interpreter of an Opaleye effect. Note that the effect itself is not actually interpreted. We do this using passthrough, which lets us perform some actions based on the Opaleye constructor and then pass them through to the upstream handler (e.g. runOpaleyeWithConnection or runOpaleyeConnection). See runOpaleyeConnectionCounting and runOpaleyeWithConnectionCounting for interpreters that do both.

Note: this function should only be used once, otherwise the operations will be tallied more than once. Unless you're sure, it's probably better to use runOpaleyeConnectionCounting or runOpaleyeWithConnectionCounting.

withCounts :: forall (es :: [Effect]) a. State SQLOperationCounts :> es => Eff es a -> Eff es (SQLOperationCounts, a) Source #

This allows us to count the number of SQL operations over the course of a sub-operation.

Pretty-printing

printCounts :: MonadIO m => SQLOperationCounts -> m () Source #

Print an SQLOperationCounts to stdout using prettyCounts. For less verbose output, see printCountsBrief.

printCountsBrief :: MonadIO m => SQLOperationCounts -> m () Source #

Print an SQLOperationCounts to stdout using prettyCountsBrief. For more verbose output, see printCounts.

renderCounts :: SQLOperationCounts -> String Source #

Render an SQLOperationCounts using prettyCounts. For less verbose output, see renderCountsBrief.

For more control over how the Doc gets rendered, use renderStyle with a custom style.

renderCountsBrief :: SQLOperationCounts -> String Source #

Render an SQLOperationCounts using prettyCountsBrief. For more verbose output, see renderCounts.

For more control over how the Doc gets rendered, use renderStyle with a custom style.

prettyCounts :: SQLOperationCounts -> Doc Source #

Pretty-print an SQLOperationCounts using Text.PrettyPrint. For each Map, we'll print one line for each table. For less verbose output, see prettyCountsBrief.

This is also the implementation of pPrint for SQLOperationCounts.

prettyCountsBrief :: SQLOperationCounts -> Doc Source #

Pretty-print an SQLOperationCounts using Text.PrettyPrint. For each Map, we'll print just the sum of the counts. For more verbose output, see prettyCounts.