{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module PGExtras.Queries.KillAll (killAllSQL, displayKillAll) where
import PGExtras.Helpers (maybeBool)
import Database.PostgreSQL.Simple
import Text.RawString.QQ
import qualified Data.Text as Text
import Control.Monad (forM_)
import Data.List (intercalate)
killAllSQL :: Query
killAllSQL :: Query
killAllSQL = [r|SELECT pg_terminate_backend(pid), 't' as t FROM pg_stat_activity
WHERE pid <> pg_backend_pid()
AND query <> '<insufficient privilege>'
AND datname = current_database();|]
displayKillAll :: [(Maybe Bool, Maybe Text.Text)] -> IO ()
displayKillAll :: [(Maybe Bool, Maybe Text)] -> IO ()
displayKillAll rows :: [(Maybe Bool, 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 Bool, Maybe Text)]
-> ((Maybe Bool, Maybe Text) -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [(Maybe Bool, Maybe Text)]
rows (((Maybe Bool, Maybe Text) -> IO ()) -> IO ())
-> ((Maybe Bool, Maybe Text) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(arg1 :: Maybe Bool
arg1, _) ->
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Bool -> String
maybeBool(Maybe Bool
arg1)
description :: [Char]
description :: String
description = "Kill all the active database connections"
tableHeaders :: [[Char]]
= ["success"]