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

module PGExtras.Queries.TotalIndexSize (totalIndexSizeSQL, displayTotalIndexSize) 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)

totalIndexSizeSQL :: Query
totalIndexSizeSQL :: Query
totalIndexSizeSQL = [r|SELECT pg_size_pretty(sum(c.relpages::bigint*8192)::bigint) AS size,
  't' as t
FROM pg_class c
LEFT JOIN pg_namespace n ON (n.oid = c.relnamespace)
WHERE n.nspname NOT IN ('pg_catalog', 'information_schema')
AND n.nspname !~ '^pg_toast'
AND c.relkind='i';|]

displayTotalIndexSize :: [(Maybe Text.Text, Maybe Text.Text)] -> IO ()
displayTotalIndexSize :: [(Maybe Text, Maybe Text)] -> IO ()
displayTotalIndexSize rows :: [(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) -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [(Maybe Text, Maybe Text)]
rows (((Maybe Text, Maybe Text) -> IO ()) -> IO ())
-> ((Maybe Text, Maybe Text) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(arg1 :: Maybe Text
arg1, _) ->
    String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Text -> String
maybeText(Maybe Text
arg1)

description :: [Char]
description :: String
description = "Total size of all indexes in MB"

tableHeaders :: [[Char]]
tableHeaders :: [String]
tableHeaders = ["size"]