{-# LANGUAGE OverloadedStrings #-}
module Database.PostgreSQL.Simple.Util
( existsTable
, withTransactionRolledBack
) where
import Control.Exception ( finally )
import Database.PostgreSQL.Simple ( Connection
, Only (..)
, begin
, query
, rollback
)
import GHC.Int (Int64)
existsTable :: Connection -> String -> IO Bool
existsTable :: Connection -> String -> IO Bool
existsTable Connection
con String
table =
[[Int64]] -> Bool
checkRowCount ([[Int64]] -> Bool) -> IO [[Int64]] -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Connection -> Query -> Only String -> IO [[Int64]]
forall q r.
(ToRow q, FromRow r) =>
Connection -> Query -> q -> IO [r]
query Connection
con Query
q (String -> Only String
forall a. a -> Only a
Only String
table) :: IO [[Int64]])
where
q :: Query
q = Query
"select count(relname) from pg_class where relname = ?"
checkRowCount :: [[Int64]] -> Bool
checkRowCount :: [[Int64]] -> Bool
checkRowCount ((Int64
1:[Int64]
_):[[Int64]]
_) = Bool
True
checkRowCount [[Int64]]
_ = Bool
False
withTransactionRolledBack :: Connection -> IO a -> IO a
withTransactionRolledBack :: Connection -> IO a -> IO a
withTransactionRolledBack Connection
con IO a
f =
Connection -> IO ()
begin Connection
con IO () -> IO a -> IO a
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO a -> IO () -> IO a
forall a b. IO a -> IO b -> IO a
finally IO a
f (Connection -> IO ()
rollback Connection
con)