{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module PGExtras.Queries.Bloat (bloatSQL, displayBloat) where
import PGExtras.Helpers (maybeText, maybeRational)
import Database.PostgreSQL.Simple
import Text.RawString.QQ
import qualified Data.Text as Text
import Control.Monad (forM_)
import Data.List (intercalate)
bloatSQL :: Query
bloatSQL :: Query
bloatSQL = [r|WITH constants AS (
SELECT current_setting('block_size')::numeric AS bs, 23 AS hdr, 4 AS ma
), bloat_info AS (
SELECT
ma,bs,schemaname,tablename,
(datawidth+(hdr+ma-(case when hdr%ma=0 THEN ma ELSE hdr%ma END)))::numeric AS datahdr,
(maxfracsum*(nullhdr+ma-(case when nullhdr%ma=0 THEN ma ELSE nullhdr%ma END))) AS nullhdr2
FROM (
SELECT
schemaname, tablename, hdr, ma, bs,
SUM((1-null_frac)*avg_width) AS datawidth,
MAX(null_frac) AS maxfracsum,
hdr+(
SELECT 1+count(*)/8
FROM pg_stats s2
WHERE null_frac<>0 AND s2.schemaname = s.schemaname AND s2.tablename = s.tablename
) AS nullhdr
FROM pg_stats s, constants
GROUP BY 1,2,3,4,5
) AS foo
), table_bloat AS (
SELECT
schemaname, tablename, cc.relpages, bs,
CEIL((cc.reltuples*((datahdr+ma-
(CASE WHEN datahdr%ma=0 THEN ma ELSE datahdr%ma END))+nullhdr2+4))/(bs-20::float)) AS otta
FROM bloat_info
JOIN pg_class cc ON cc.relname = bloat_info.tablename
JOIN pg_namespace nn ON cc.relnamespace = nn.oid AND nn.nspname = bloat_info.schemaname AND nn.nspname <> 'information_schema'
), index_bloat AS (
SELECT
schemaname, tablename, bs,
COALESCE(c2.relname,'?') AS iname, COALESCE(c2.reltuples,0) AS ituples, COALESCE(c2.relpages,0) AS ipages,
COALESCE(CEIL((c2.reltuples*(datahdr-12))/(bs-20::float)),0) AS iotta -- very rough approximation, assumes all cols
FROM bloat_info
JOIN pg_class cc ON cc.relname = bloat_info.tablename
JOIN pg_namespace nn ON cc.relnamespace = nn.oid AND nn.nspname = bloat_info.schemaname AND nn.nspname <> 'information_schema'
JOIN pg_index i ON indrelid = cc.oid
JOIN pg_class c2 ON c2.oid = i.indexrelid
)
SELECT
type, schemaname, object_name, bloat, pg_size_pretty(raw_waste) as waste
FROM
(SELECT
'table' as type,
schemaname,
tablename as object_name,
ROUND(CASE WHEN otta=0 THEN 0.0 ELSE table_bloat.relpages/otta::numeric END,1) AS bloat,
CASE WHEN relpages < otta THEN '0' ELSE (bs*(table_bloat.relpages-otta)::bigint)::bigint END AS raw_waste
FROM
table_bloat
UNION
SELECT
'index' as type,
schemaname,
tablename || '::' || iname as object_name,
ROUND(CASE WHEN iotta=0 OR ipages=0 THEN 0.0 ELSE ipages/iotta::numeric END,1) AS bloat,
CASE WHEN ipages < iotta THEN '0' ELSE (bs*(ipages-iotta))::bigint END AS raw_waste
FROM
index_bloat) bloat_summary
ORDER BY raw_waste DESC, bloat DESC;|]
displayBloat :: [(Maybe Text.Text, Maybe Text.Text, Maybe Text.Text, Maybe Rational, Maybe Text.Text)] -> IO ()
displayBloat :: [(Maybe Text, Maybe Text, Maybe Text, Maybe Rational, Maybe Text)]
-> IO ()
displayBloat rows :: [(Maybe Text, Maybe Text, Maybe Text, Maybe Rational, 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 Rational, Maybe Text)]
-> ((Maybe Text, Maybe Text, Maybe Text, Maybe Rational,
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 Rational, Maybe Text)]
rows (((Maybe Text, Maybe Text, Maybe Text, Maybe Rational, Maybe Text)
-> IO ())
-> IO ())
-> ((Maybe Text, Maybe Text, Maybe Text, Maybe Rational,
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 Rational
arg4, arg5 :: Maybe Text
arg5) ->
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 Rational -> String
maybeRational(Maybe Rational
arg4) String -> String -> String
forall a. [a] -> [a] -> [a]
++ " | " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Maybe Text -> String
maybeText(Maybe Text
arg5)
description :: [Char]
description :: String
description = "Table and index bloat in your database ordered by most wasteful"
tableHeaders :: [[Char]]
= ["type", "schemaname", "object_name", "bloat", "waste"]