{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}

module PGExtras.Queries.Blocking (blockingSQL, displayBlocking) where

import PGExtras.Helpers (maybeText)
import Database.PostgreSQL.Simple
import Text.RawString.QQ
import qualified Data.Text as Text
import Control.Monad (forM_)
import Data.List (intercalate)

blockingSQL :: Query
blockingSQL :: Query
blockingSQL = [r|SELECT bl.pid AS blocked_pid,
  ka.query AS blocking_statement,
  now() - ka.query_start AS blocking_duration,
  kl.pid AS blocking_pid,
  a.query AS blocked_statement,
  now() - a.query_start AS blocked_duration
FROM pg_catalog.pg_locks bl
JOIN pg_catalog.pg_stat_activity a
  ON bl.pid = a.pid
JOIN pg_catalog.pg_locks kl
  JOIN pg_catalog.pg_stat_activity ka
    ON kl.pid = ka.pid
ON bl.transactionid = kl.transactionid AND bl.pid != kl.pid
WHERE NOT bl.granted;|]

displayBlocking :: [(Maybe Text.Text, Maybe Text.Text, Maybe Text.Text, Maybe Text.Text, Maybe Text.Text, Maybe Text.Text)] -> IO ()
displayBlocking :: [(Maybe Text, Maybe Text, Maybe Text, Maybe Text, Maybe Text,
  Maybe Text)]
-> IO ()
displayBlocking rows :: [(Maybe Text, Maybe Text, Maybe Text, Maybe Text, Maybe Text,
  Maybe Text)]
rows = do
  String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
description
  String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate " | " [String]
tableHeaders
  [(Maybe Text, Maybe Text, Maybe Text, Maybe Text, Maybe Text,
  Maybe Text)]
-> ((Maybe Text, Maybe Text, Maybe Text, Maybe Text, Maybe Text,
     Maybe Text)
    -> IO ())
-> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [(Maybe Text, Maybe Text, Maybe Text, Maybe Text, Maybe Text,
  Maybe Text)]
rows (((Maybe Text, Maybe Text, Maybe Text, Maybe Text, Maybe Text,
   Maybe Text)
  -> IO ())
 -> IO ())
-> ((Maybe Text, Maybe Text, Maybe Text, Maybe Text, Maybe Text,
     Maybe Text)
    -> IO ())
-> IO ()
forall a b. (a -> b) -> a -> b
$ \(arg1 :: Maybe Text
arg1, arg2 :: Maybe Text
arg2, arg3 :: Maybe Text
arg3, arg4 :: Maybe Text
arg4, arg5 :: Maybe Text
arg5, arg6 :: Maybe Text
arg6) ->
    String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Text -> String
maybeText(Maybe Text
arg1) String -> String -> String
forall a. [a] -> [a] -> [a]
++ " | " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Maybe Text -> String
maybeText(Maybe Text
arg2) String -> String -> String
forall a. [a] -> [a] -> [a]
++ " | " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Maybe Text -> String
maybeText(Maybe Text
arg3) String -> String -> String
forall a. [a] -> [a] -> [a]
++ " | " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Maybe Text -> String
maybeText(Maybe Text
arg4) String -> String -> String
forall a. [a] -> [a] -> [a]
++ " | " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Maybe Text -> String
maybeText(Maybe Text
arg5) String -> String -> String
forall a. [a] -> [a] -> [a]
++ " | " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Maybe Text -> String
maybeText(Maybe Text
arg6)

description :: [Char]
description :: String
description = "Queries holding locks other queries are waiting to be released"

tableHeaders :: [[Char]]
tableHeaders :: [String]
tableHeaders = ["blocked_pid", "blocking_statement", "blocking_duration", "blocking_pid", "blocked_statement", "blocked_duration"]