{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module PGExtras.Queries.UnusedIndexes (unusedIndexesSQL, displayUnusedIndexes) where
import PGExtras.Helpers (maybeText, maybeInt)
import Database.PostgreSQL.Simple
import Text.RawString.QQ
import qualified Data.Text as Text
import Control.Monad (forM_)
import Data.List (intercalate)
unusedIndexesSQL :: Query
unusedIndexesSQL :: Query
unusedIndexesSQL = [r|SELECT
schemaname || '.' || relname AS table,
indexrelname AS index,
pg_size_pretty(pg_relation_size(i.indexrelid)) AS index_size,
idx_scan as index_scans
FROM pg_stat_user_indexes ui
JOIN pg_index i ON ui.indexrelid = i.indexrelid
WHERE NOT indisunique AND idx_scan < 50 AND pg_relation_size(relid) > 5 * 8192
ORDER BY pg_relation_size(i.indexrelid) / nullif(idx_scan, 0) DESC NULLS FIRST,
pg_relation_size(i.indexrelid) DESC;|]
displayUnusedIndexes :: [(Maybe Text.Text, Maybe Text.Text, Maybe Text.Text, Maybe Int)] -> IO ()
displayUnusedIndexes :: [(Maybe Text, Maybe Text, Maybe Text, Maybe Int)] -> IO ()
displayUnusedIndexes rows :: [(Maybe Text, Maybe Text, Maybe Text, Maybe Int)]
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 Int)]
-> ((Maybe Text, Maybe Text, Maybe Text, Maybe Int) -> 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 Int)]
rows (((Maybe Text, Maybe Text, Maybe Text, Maybe Int) -> IO ())
-> IO ())
-> ((Maybe Text, Maybe Text, Maybe Text, Maybe Int) -> IO ())
-> IO ()
forall a b. (a -> b) -> a -> b
$ \(arg1 :: Maybe Text
arg1, arg2 :: Maybe Text
arg2, arg3 :: Maybe Text
arg3, arg4 :: Maybe Int
arg4) ->
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 Int -> String
maybeInt(Maybe Int
arg4)
description :: [Char]
description :: String
description = "Unused and almost unused indexes"
tableHeaders :: [[Char]]
= ["name", "ratio"]