module Refurb.MigrationUtils where
import ClassyPrelude
import Control.Monad.Logger (logDebug)
import Data.Profunctor.Product.Default (Default)
import qualified Data.Text as T
import qualified Database.PostgreSQL.Simple as PG
import Database.PostgreSQL.Simple.ToRow (toRow)
import Database.PostgreSQL.Simple.Types (fromQuery)
import qualified Language.Haskell.TH.Syntax as TH
import qualified Language.Haskell.TH.Quote as TH
import qualified Opaleye
import Opaleye.Internal.Table (tableIdentifier)
import Refurb.Types (MonadMigration)
qqSql :: TH.QuasiQuoter
qqSql = TH.QuasiQuoter
{ TH.quoteExp = \ s -> [| $(TH.lift s) :: PG.Query |]
, TH.quotePat = error "qqSql should only be used in an expression context"
, TH.quoteType = error "qqSql should only be used in an expression context"
, TH.quoteDec = error "qqSql should only be used in an expression context"
}
qqSqls :: TH.QuasiQuoter
qqSqls = TH.QuasiQuoter
{ TH.quoteExp = \ s -> [| $(bodyToStatements s) :: [PG.Query] |]
, TH.quotePat = error "qqSql should only be used in an expression context"
, TH.quoteType = error "qqSql should only be used in an expression context"
, TH.quoteDec = error "qqSql should only be used in an expression context"
}
where
bodyToStatements :: String -> TH.Q TH.Exp
bodyToStatements = TH.lift . map (unpack . unlines) . filter (not . null) . map (filter (not . null)) . go [] . lines . pack
where
go acc [] = [acc]
go acc ((T.strip -> l):ls)
| Just l' <- T.stripSuffix ";" =<< T.stripPrefix ";" l =
reverse acc : [l'] : go [] ls
| Just l' <- T.stripPrefix ";" l =
reverse acc : go [l'] ls
| Just l' <- T.stripSuffix ";" l =
reverse (l' : acc) : go [] ls
| otherwise =
go (l : acc) ls
execute :: (MonadMigration m, PG.ToRow q) => PG.Query -> q -> m Int64
execute q p = do
conn <- ask
$logDebug $ decodeUtf8 (fromQuery q) <> " with " <> tshow (toRow p)
liftBase $ PG.execute conn q p
executeMany :: (MonadMigration m, PG.ToRow q) => PG.Query -> [q] -> m Int64
executeMany q ps = do
conn <- ask
$logDebug $ decodeUtf8 (fromQuery q) <> " with ["
<> maybe "" ((if length ps > 1 then (<> ", ...") else id) . tshow . toRow) (headMay ps) <> "]"
liftBase $ PG.executeMany conn q ps
execute_ :: MonadMigration m => PG.Query -> m Int64
execute_ q = do
conn <- ask
$logDebug . decodeUtf8 $ fromQuery q
liftBase $ PG.execute_ conn q
executeSeries_ :: MonadMigration m => [PG.Query] -> m ()
executeSeries_ = traverse_ (void . execute_)
query :: (MonadMigration m, PG.ToRow q, PG.FromRow r) => PG.Query -> q -> m [r]
query q p = do
conn <- ask
$logDebug $ decodeUtf8 (fromQuery q) <> " with " <> tshow (toRow p)
liftBase $ PG.query conn q p
query_ :: (MonadMigration m, PG.FromRow r) => PG.Query -> m [r]
query_ q = do
conn <- ask
$logDebug . decodeUtf8 $ fromQuery q
liftBase $ PG.query_ conn q
runQuery
:: ( MonadMigration m
, Default Opaleye.Unpackspec columns columns
, Default Opaleye.QueryRunner columns haskells
)
=> Opaleye.Query columns -> m [haskells]
runQuery q = do
conn <- ask
for_ (Opaleye.showSql q) ($logDebug . pack)
liftBase $ Opaleye.runQuery conn q
runInsertMany :: MonadMigration m => Opaleye.Table columns columns' -> [columns] -> m Int64
runInsertMany table rows = do
conn <- ask
$logDebug $ "inserting " <> tshow (length rows) <> " rows into " <> tshow (tableIdentifier table)
liftBase $ Opaleye.runInsertMany conn table rows
runUpdate :: MonadMigration m => Opaleye.Table columnsW columnsR -> (columnsR -> columnsW) -> (columnsR -> Opaleye.Column Opaleye.PGBool) -> m Int64
runUpdate table permute filt = do
conn <- ask
$logDebug $ "updating " <> tshow (tableIdentifier table)
liftBase $ Opaleye.runUpdate conn table permute filt
runDelete :: MonadMigration m => Opaleye.Table columnsW columnsR -> (columnsR -> Opaleye.Column Opaleye.PGBool) -> m Int64
runDelete table filt = do
conn <- ask
$logDebug $ "deleting from " <> tshow (tableIdentifier table)
liftBase $ Opaleye.runDelete conn table filt
doesSchemaExist :: MonadMigration m => Text -> m Bool
doesSchemaExist schema =
not . (null :: [PG.Only Int] -> Bool) <$> query "select 1 from information_schema.schemata where schema_name = ?" (PG.Only schema)
doesTableExist :: MonadMigration m => Text -> Text -> m Bool
doesTableExist schema table =
not . (null :: [PG.Only Int] -> Bool) <$> query "select 1 from information_schema.tables where table_schema = ? and table_name = ?" (schema, table)