{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}

#if MIN_VERSION_base(4,12,0)
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
#endif

-- | A postgresql backend for persistent.
module Database.Persist.Postgresql
    ( withPostgresqlPool
    , withPostgresqlPoolWithVersion
    , withPostgresqlConn
    , withPostgresqlConnWithVersion
    , withPostgresqlPoolWithConf
    , createPostgresqlPool
    , createPostgresqlPoolModified
    , createPostgresqlPoolModifiedWithVersion
    , createPostgresqlPoolWithConf
    , module Database.Persist.Sql
    , ConnectionString
    , HandleUpdateCollision
    , copyField
    , copyUnlessNull
    , copyUnlessEmpty
    , copyUnlessEq
    , excludeNotEqualToOriginal
    , PostgresConf (..)
    , PgInterval (..)
    , upsertWhere
    , upsertManyWhere
    , openSimpleConn
    , openSimpleConnWithVersion
    , getSimpleConn
    , tableName
    , fieldName
    , mockMigration
    , migrateEnableExtension
    , PostgresConfHooks(..)
    , defaultPostgresConfHooks

    , RawPostgresql(..)
    , createRawPostgresqlPool
    , createRawPostgresqlPoolModified
    , createRawPostgresqlPoolModifiedWithVersion
    , createRawPostgresqlPoolWithConf
    ) where

import qualified Database.PostgreSQL.LibPQ as LibPQ

import qualified Database.PostgreSQL.Simple as PG
import qualified Database.PostgreSQL.Simple.FromField as PGFF
import qualified Database.PostgreSQL.Simple.Internal as PG
import Database.PostgreSQL.Simple.Ok (Ok(..))
import qualified Database.PostgreSQL.Simple.Transaction as PG
import qualified Database.PostgreSQL.Simple.Types as PG

import Control.Arrow
import Control.Exception (Exception, throw, throwIO)
import Control.Monad
import Control.Monad.Except
import Control.Monad.IO.Unlift (MonadIO(..), MonadUnliftIO)
import Control.Monad.Logger (MonadLoggerIO, runNoLoggingT)
import Control.Monad.Trans.Reader (ReaderT(..), asks, runReaderT)
#if !MIN_VERSION_base(4,12,0)
import Control.Monad.Trans.Reader (withReaderT)
#endif
import Control.Monad.Trans.Writer (WriterT(..), runWriterT)
import qualified Data.List.NonEmpty as NEL
import Data.Proxy (Proxy(..))

import Data.Acquire (Acquire, mkAcquire, with)
import Data.Aeson
import Data.Aeson.Types (modifyFailure)
import qualified Data.Attoparsec.Text as AT
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as B8
import Data.Conduit
import qualified Data.Conduit.List as CL
import Data.Data (Data)
import Data.Either (partitionEithers)
import Data.Function (on)
import Data.IORef
import Data.Int (Int64)
import Data.List (find, foldl', groupBy, sort)
import qualified Data.List as List
import Data.List.NonEmpty (NonEmpty)
import qualified Data.Map as Map
import Data.Maybe
import Data.Monoid ((<>))
import qualified Data.Monoid as Monoid
import Data.Pool (Pool)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T
import Data.Text.Read (rational)
import System.Environment (getEnvironment)

#if MIN_VERSION_base(4,12,0)
import Database.Persist.Compatible
#endif
import Database.Persist.Postgresql.Internal
import Database.Persist.Sql
import qualified Database.Persist.Sql.Util as Util
import Database.Persist.SqlBackend
import Database.Persist.SqlBackend.StatementCache (StatementCache, mkSimpleStatementCache, mkStatementCache)
import qualified Data.Vault.Strict as Vault
import System.IO.Unsafe (unsafePerformIO)

-- | A @libpq@ connection string.  A simple example of connection
-- string would be @\"host=localhost port=5432 user=test
-- dbname=test password=test\"@.  Please read libpq's
-- documentation at
-- <https://www.postgresql.org/docs/current/static/libpq-connect.html>
-- for more details on how to create such strings.
type ConnectionString = ByteString

-- | PostgresServerVersionError exception. This is thrown when persistent
-- is unable to find the version of the postgreSQL server.
data PostgresServerVersionError = PostgresServerVersionError String

instance Show PostgresServerVersionError where
    show :: PostgresServerVersionError -> String
show (PostgresServerVersionError String
uniqueMsg) =
      String
"Unexpected PostgreSQL server version, got " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
uniqueMsg
instance Exception PostgresServerVersionError

-- | Create a PostgreSQL connection pool and run the given action. The pool is
-- properly released after the action finishes using it.  Note that you should
-- not use the given 'ConnectionPool' outside the action since it may already
-- have been released.
-- The provided action should use 'runSqlConn' and *not* 'runReaderT' because
-- the former brackets the database action with transaction begin/commit.
withPostgresqlPool :: (MonadLoggerIO m, MonadUnliftIO m)
                   => ConnectionString
                   -- ^ Connection string to the database.
                   -> Int
                   -- ^ Number of connections to be kept open in
                   -- the pool.
                   -> (Pool SqlBackend -> m a)
                   -- ^ Action to be executed that uses the
                   -- connection pool.
                   -> m a
withPostgresqlPool :: ConnectionString -> Int -> (Pool SqlBackend -> m a) -> m a
withPostgresqlPool ConnectionString
ci = (Connection -> IO (Maybe Double))
-> ConnectionString -> Int -> (Pool SqlBackend -> m a) -> m a
forall (m :: * -> *) a.
(MonadUnliftIO m, MonadLoggerIO m) =>
(Connection -> IO (Maybe Double))
-> ConnectionString -> Int -> (Pool SqlBackend -> m a) -> m a
withPostgresqlPoolWithVersion Connection -> IO (Maybe Double)
getServerVersion ConnectionString
ci

-- | Same as 'withPostgresPool', but takes a callback for obtaining
-- the server version (to work around an Amazon Redshift bug).
--
-- @since 2.6.2
withPostgresqlPoolWithVersion :: (MonadUnliftIO m, MonadLoggerIO m)
                              => (PG.Connection -> IO (Maybe Double))
                              -- ^ Action to perform to get the server version.
                              -> ConnectionString
                              -- ^ Connection string to the database.
                              -> Int
                              -- ^ Number of connections to be kept open in
                              -- the pool.
                              -> (Pool SqlBackend -> m a)
                              -- ^ Action to be executed that uses the
                              -- connection pool.
                              -> m a
withPostgresqlPoolWithVersion :: (Connection -> IO (Maybe Double))
-> ConnectionString -> Int -> (Pool SqlBackend -> m a) -> m a
withPostgresqlPoolWithVersion Connection -> IO (Maybe Double)
getVerDouble ConnectionString
ci = do
  let getVer :: Connection -> IO (NonEmpty Word)
getVer = (Connection -> IO (Maybe Double))
-> Connection -> IO (NonEmpty Word)
oldGetVersionToNew Connection -> IO (Maybe Double)
getVerDouble
  (LogFunc -> IO SqlBackend)
-> Int -> (Pool SqlBackend -> m a) -> m a
forall backend (m :: * -> *) a.
(MonadLoggerIO m, MonadUnliftIO m,
 BackendCompatible SqlBackend backend) =>
(LogFunc -> IO backend) -> Int -> (Pool backend -> m a) -> m a
withSqlPool ((LogFunc -> IO SqlBackend)
 -> Int -> (Pool SqlBackend -> m a) -> m a)
-> (LogFunc -> IO SqlBackend)
-> Int
-> (Pool SqlBackend -> m a)
-> m a
forall a b. (a -> b) -> a -> b
$ (Connection -> IO ())
-> (Connection -> IO (NonEmpty Word))
-> ((Connection -> SqlBackend) -> Connection -> SqlBackend)
-> ConnectionString
-> LogFunc
-> IO SqlBackend
forall backend.
(Connection -> IO ())
-> (Connection -> IO (NonEmpty Word))
-> ((Connection -> SqlBackend) -> Connection -> backend)
-> ConnectionString
-> LogFunc
-> IO backend
open' (IO () -> Connection -> IO ()
forall a b. a -> b -> a
const (IO () -> Connection -> IO ()) -> IO () -> Connection -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) Connection -> IO (NonEmpty Word)
getVer (Connection -> SqlBackend) -> Connection -> SqlBackend
forall a. a -> a
id ConnectionString
ci

-- | Same as 'withPostgresqlPool', but can be configured with 'PostgresConf' and 'PostgresConfHooks'.
--
-- @since 2.11.0.0
withPostgresqlPoolWithConf :: (MonadUnliftIO m, MonadLoggerIO m)
                           => PostgresConf -- ^ Configuration for connecting to Postgres
                           -> PostgresConfHooks -- ^ Record of callback functions
                           -> (Pool SqlBackend -> m a)
                           -- ^ Action to be executed that uses the
                           -- connection pool.
                           -> m a
withPostgresqlPoolWithConf :: PostgresConf
-> PostgresConfHooks -> (Pool SqlBackend -> m a) -> m a
withPostgresqlPoolWithConf PostgresConf
conf PostgresConfHooks
hooks = do
  let getVer :: Connection -> IO (NonEmpty Word)
getVer = PostgresConfHooks -> Connection -> IO (NonEmpty Word)
pgConfHooksGetServerVersion PostgresConfHooks
hooks
      modConn :: Connection -> IO ()
modConn = PostgresConfHooks -> Connection -> IO ()
pgConfHooksAfterCreate PostgresConfHooks
hooks
  let logFuncToBackend :: LogFunc -> IO SqlBackend
logFuncToBackend = (Connection -> IO ())
-> (Connection -> IO (NonEmpty Word))
-> ((Connection -> SqlBackend) -> Connection -> SqlBackend)
-> ConnectionString
-> LogFunc
-> IO SqlBackend
forall backend.
(Connection -> IO ())
-> (Connection -> IO (NonEmpty Word))
-> ((Connection -> SqlBackend) -> Connection -> backend)
-> ConnectionString
-> LogFunc
-> IO backend
open' Connection -> IO ()
modConn Connection -> IO (NonEmpty Word)
getVer (Connection -> SqlBackend) -> Connection -> SqlBackend
forall a. a -> a
id (PostgresConf -> ConnectionString
pgConnStr PostgresConf
conf)
  (LogFunc -> IO SqlBackend)
-> ConnectionPoolConfig -> (Pool SqlBackend -> m a) -> m a
forall backend (m :: * -> *) a.
(MonadLoggerIO m, MonadUnliftIO m,
 BackendCompatible SqlBackend backend) =>
(LogFunc -> IO backend)
-> ConnectionPoolConfig -> (Pool backend -> m a) -> m a
withSqlPoolWithConfig LogFunc -> IO SqlBackend
logFuncToBackend (PostgresConf -> ConnectionPoolConfig
postgresConfToConnectionPoolConfig PostgresConf
conf)

-- | Create a PostgreSQL connection pool.  Note that it's your
-- responsibility to properly close the connection pool when
-- unneeded.  Use 'withPostgresqlPool' for an automatic resource
-- control.
createPostgresqlPool :: (MonadUnliftIO m, MonadLoggerIO m)
                     => ConnectionString
                     -- ^ Connection string to the database.
                     -> Int
                     -- ^ Number of connections to be kept open
                     -- in the pool.
                     -> m (Pool SqlBackend)
createPostgresqlPool :: ConnectionString -> Int -> m (Pool SqlBackend)
createPostgresqlPool = (Connection -> IO ())
-> ConnectionString -> Int -> m (Pool SqlBackend)
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
(Connection -> IO ())
-> ConnectionString -> Int -> m (Pool SqlBackend)
createPostgresqlPoolModified (IO () -> Connection -> IO ()
forall a b. a -> b -> a
const (IO () -> Connection -> IO ()) -> IO () -> Connection -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())

-- | Same as 'createPostgresqlPool', but additionally takes a callback function
-- for some connection-specific tweaking to be performed after connection
-- creation. This could be used, for example, to change the schema. For more
-- information, see:
--
-- <https://groups.google.com/d/msg/yesodweb/qUXrEN_swEo/O0pFwqwQIdcJ>
--
-- @since 2.1.3
createPostgresqlPoolModified
    :: (MonadUnliftIO m, MonadLoggerIO m)
    => (PG.Connection -> IO ()) -- ^ Action to perform after connection is created.
    -> ConnectionString -- ^ Connection string to the database.
    -> Int -- ^ Number of connections to be kept open in the pool.
    -> m (Pool SqlBackend)
createPostgresqlPoolModified :: (Connection -> IO ())
-> ConnectionString -> Int -> m (Pool SqlBackend)
createPostgresqlPoolModified = (Connection -> IO (Maybe Double))
-> (Connection -> IO ())
-> ConnectionString
-> Int
-> m (Pool SqlBackend)
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
(Connection -> IO (Maybe Double))
-> (Connection -> IO ())
-> ConnectionString
-> Int
-> m (Pool SqlBackend)
createPostgresqlPoolModifiedWithVersion Connection -> IO (Maybe Double)
getServerVersion

-- | Same as other similarly-named functions in this module, but takes callbacks for obtaining
-- the server version (to work around an Amazon Redshift bug) and connection-specific tweaking
-- (to change the schema).
--
-- @since 2.6.2
createPostgresqlPoolModifiedWithVersion
    :: (MonadUnliftIO m, MonadLoggerIO m)
    => (PG.Connection -> IO (Maybe Double)) -- ^ Action to perform to get the server version.
    -> (PG.Connection -> IO ()) -- ^ Action to perform after connection is created.
    -> ConnectionString -- ^ Connection string to the database.
    -> Int -- ^ Number of connections to be kept open in the pool.
    -> m (Pool SqlBackend)
createPostgresqlPoolModifiedWithVersion :: (Connection -> IO (Maybe Double))
-> (Connection -> IO ())
-> ConnectionString
-> Int
-> m (Pool SqlBackend)
createPostgresqlPoolModifiedWithVersion Connection -> IO (Maybe Double)
getVerDouble Connection -> IO ()
modConn ConnectionString
ci = do
  let getVer :: Connection -> IO (NonEmpty Word)
getVer = (Connection -> IO (Maybe Double))
-> Connection -> IO (NonEmpty Word)
oldGetVersionToNew Connection -> IO (Maybe Double)
getVerDouble
  (LogFunc -> IO SqlBackend) -> Int -> m (Pool SqlBackend)
forall backend (m :: * -> *).
(MonadLoggerIO m, MonadUnliftIO m,
 BackendCompatible SqlBackend backend) =>
(LogFunc -> IO backend) -> Int -> m (Pool backend)
createSqlPool ((LogFunc -> IO SqlBackend) -> Int -> m (Pool SqlBackend))
-> (LogFunc -> IO SqlBackend) -> Int -> m (Pool SqlBackend)
forall a b. (a -> b) -> a -> b
$ (Connection -> IO ())
-> (Connection -> IO (NonEmpty Word))
-> ((Connection -> SqlBackend) -> Connection -> SqlBackend)
-> ConnectionString
-> LogFunc
-> IO SqlBackend
forall backend.
(Connection -> IO ())
-> (Connection -> IO (NonEmpty Word))
-> ((Connection -> SqlBackend) -> Connection -> backend)
-> ConnectionString
-> LogFunc
-> IO backend
open' Connection -> IO ()
modConn Connection -> IO (NonEmpty Word)
getVer (Connection -> SqlBackend) -> Connection -> SqlBackend
forall a. a -> a
id ConnectionString
ci

-- | Same as 'createPostgresqlPool', but can be configured with 'PostgresConf' and 'PostgresConfHooks'.
--
-- @since 2.11.0.0
createPostgresqlPoolWithConf
    :: (MonadUnliftIO m, MonadLoggerIO m)
    => PostgresConf -- ^ Configuration for connecting to Postgres
    -> PostgresConfHooks -- ^ Record of callback functions
    -> m (Pool SqlBackend)
createPostgresqlPoolWithConf :: PostgresConf -> PostgresConfHooks -> m (Pool SqlBackend)
createPostgresqlPoolWithConf PostgresConf
conf PostgresConfHooks
hooks = do
  let getVer :: Connection -> IO (NonEmpty Word)
getVer = PostgresConfHooks -> Connection -> IO (NonEmpty Word)
pgConfHooksGetServerVersion PostgresConfHooks
hooks
      modConn :: Connection -> IO ()
modConn = PostgresConfHooks -> Connection -> IO ()
pgConfHooksAfterCreate PostgresConfHooks
hooks
  (LogFunc -> IO SqlBackend)
-> ConnectionPoolConfig -> m (Pool SqlBackend)
forall (m :: * -> *) backend.
(MonadLoggerIO m, MonadUnliftIO m,
 BackendCompatible SqlBackend backend) =>
(LogFunc -> IO backend) -> ConnectionPoolConfig -> m (Pool backend)
createSqlPoolWithConfig ((Connection -> IO ())
-> (Connection -> IO (NonEmpty Word))
-> ((Connection -> SqlBackend) -> Connection -> SqlBackend)
-> ConnectionString
-> LogFunc
-> IO SqlBackend
forall backend.
(Connection -> IO ())
-> (Connection -> IO (NonEmpty Word))
-> ((Connection -> SqlBackend) -> Connection -> backend)
-> ConnectionString
-> LogFunc
-> IO backend
open' Connection -> IO ()
modConn Connection -> IO (NonEmpty Word)
getVer (Connection -> SqlBackend) -> Connection -> SqlBackend
forall a. a -> a
id (PostgresConf -> ConnectionString
pgConnStr PostgresConf
conf)) (PostgresConf -> ConnectionPoolConfig
postgresConfToConnectionPoolConfig PostgresConf
conf)

postgresConfToConnectionPoolConfig :: PostgresConf -> ConnectionPoolConfig
postgresConfToConnectionPoolConfig :: PostgresConf -> ConnectionPoolConfig
postgresConfToConnectionPoolConfig PostgresConf
conf =
  ConnectionPoolConfig :: Int -> NominalDiffTime -> Int -> ConnectionPoolConfig
ConnectionPoolConfig
    { connectionPoolConfigStripes :: Int
connectionPoolConfigStripes = PostgresConf -> Int
pgPoolStripes PostgresConf
conf
    , connectionPoolConfigIdleTimeout :: NominalDiffTime
connectionPoolConfigIdleTimeout = Integer -> NominalDiffTime
forall a. Num a => Integer -> a
fromInteger (Integer -> NominalDiffTime) -> Integer -> NominalDiffTime
forall a b. (a -> b) -> a -> b
$ PostgresConf -> Integer
pgPoolIdleTimeout PostgresConf
conf
    , connectionPoolConfigSize :: Int
connectionPoolConfigSize = PostgresConf -> Int
pgPoolSize PostgresConf
conf
    }

-- | Same as 'withPostgresqlPool', but instead of opening a pool
-- of connections, only one connection is opened.
-- The provided action should use 'runSqlConn' and *not* 'runReaderT' because
-- the former brackets the database action with transaction begin/commit.
withPostgresqlConn :: (MonadUnliftIO m, MonadLoggerIO m)
                   => ConnectionString -> (SqlBackend -> m a) -> m a
withPostgresqlConn :: ConnectionString -> (SqlBackend -> m a) -> m a
withPostgresqlConn = (Connection -> IO (Maybe Double))
-> ConnectionString -> (SqlBackend -> m a) -> m a
forall (m :: * -> *) a.
(MonadUnliftIO m, MonadLoggerIO m) =>
(Connection -> IO (Maybe Double))
-> ConnectionString -> (SqlBackend -> m a) -> m a
withPostgresqlConnWithVersion Connection -> IO (Maybe Double)
getServerVersion

-- | Same as 'withPostgresqlConn', but takes a callback for obtaining
-- the server version (to work around an Amazon Redshift bug).
--
-- @since 2.6.2
withPostgresqlConnWithVersion :: (MonadUnliftIO m, MonadLoggerIO m)
                              => (PG.Connection -> IO (Maybe Double))
                              -> ConnectionString
                              -> (SqlBackend -> m a)
                              -> m a
withPostgresqlConnWithVersion :: (Connection -> IO (Maybe Double))
-> ConnectionString -> (SqlBackend -> m a) -> m a
withPostgresqlConnWithVersion Connection -> IO (Maybe Double)
getVerDouble = do
  let getVer :: Connection -> IO (NonEmpty Word)
getVer = (Connection -> IO (Maybe Double))
-> Connection -> IO (NonEmpty Word)
oldGetVersionToNew Connection -> IO (Maybe Double)
getVerDouble
  (LogFunc -> IO SqlBackend) -> (SqlBackend -> m a) -> m a
forall backend (m :: * -> *) a.
(MonadUnliftIO m, MonadLoggerIO m,
 BackendCompatible SqlBackend backend) =>
(LogFunc -> IO backend) -> (backend -> m a) -> m a
withSqlConn ((LogFunc -> IO SqlBackend) -> (SqlBackend -> m a) -> m a)
-> (ConnectionString -> LogFunc -> IO SqlBackend)
-> ConnectionString
-> (SqlBackend -> m a)
-> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Connection -> IO ())
-> (Connection -> IO (NonEmpty Word))
-> ((Connection -> SqlBackend) -> Connection -> SqlBackend)
-> ConnectionString
-> LogFunc
-> IO SqlBackend
forall backend.
(Connection -> IO ())
-> (Connection -> IO (NonEmpty Word))
-> ((Connection -> SqlBackend) -> Connection -> backend)
-> ConnectionString
-> LogFunc
-> IO backend
open' (IO () -> Connection -> IO ()
forall a b. a -> b -> a
const (IO () -> Connection -> IO ()) -> IO () -> Connection -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) Connection -> IO (NonEmpty Word)
getVer (Connection -> SqlBackend) -> Connection -> SqlBackend
forall a. a -> a
id

open'
    :: (PG.Connection -> IO ())
    -> (PG.Connection -> IO (NonEmpty Word))
    -> ((PG.Connection -> SqlBackend) -> PG.Connection -> backend)
    -- ^ How to construct the actual backend type desired. For most uses,
    -- this is just 'id', since the desired backend type is 'SqlBackend'.
    -- But some callers want a @'RawPostgresql' 'SqlBackend'@, and will
    -- pass in 'withRawConnection'.
    -> ConnectionString -> LogFunc -> IO backend
open' :: (Connection -> IO ())
-> (Connection -> IO (NonEmpty Word))
-> ((Connection -> SqlBackend) -> Connection -> backend)
-> ConnectionString
-> LogFunc
-> IO backend
open' Connection -> IO ()
modConn Connection -> IO (NonEmpty Word)
getVer (Connection -> SqlBackend) -> Connection -> backend
constructor ConnectionString
cstr LogFunc
logFunc = do
    Connection
conn <- ConnectionString -> IO Connection
PG.connectPostgreSQL ConnectionString
cstr
    Connection -> IO ()
modConn Connection
conn
    NonEmpty Word
ver <- Connection -> IO (NonEmpty Word)
getVer Connection
conn
    IORef (Map Text Statement)
smap <- Map Text Statement -> IO (IORef (Map Text Statement))
forall a. a -> IO (IORef a)
newIORef Map Text Statement
forall a. Monoid a => a
mempty
    backend -> IO backend
forall (m :: * -> *) a. Monad m => a -> m a
return (backend -> IO backend) -> backend -> IO backend
forall a b. (a -> b) -> a -> b
$ (Connection -> SqlBackend) -> Connection -> backend
constructor (LogFunc
-> NonEmpty Word
-> IORef (Map Text Statement)
-> Connection
-> SqlBackend
createBackend LogFunc
logFunc NonEmpty Word
ver IORef (Map Text Statement)
smap) Connection
conn

-- | Gets the PostgreSQL server version
getServerVersion :: PG.Connection -> IO (Maybe Double)
getServerVersion :: Connection -> IO (Maybe Double)
getServerVersion Connection
conn = do
  [PG.Only Text
version] <- Connection -> Query -> IO [Only Text]
forall r. FromRow r => Connection -> Query -> IO [r]
PG.query_ Connection
conn Query
"show server_version";
  let version' :: Either String (Double, Text)
version' = Reader Double
forall a. Fractional a => Reader a
rational Text
version
  --- λ> rational "9.8.3"
  --- Right (9.8,".3")
  --- λ> rational "9.8.3.5"
  --- Right (9.8,".3.5")
  case Either String (Double, Text)
version' of
    Right (Double
a,Text
_) -> Maybe Double -> IO (Maybe Double)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Double -> IO (Maybe Double))
-> Maybe Double -> IO (Maybe Double)
forall a b. (a -> b) -> a -> b
$ Double -> Maybe Double
forall a. a -> Maybe a
Just Double
a
    Left String
err -> PostgresServerVersionError -> IO (Maybe Double)
forall e a. Exception e => e -> IO a
throwIO (PostgresServerVersionError -> IO (Maybe Double))
-> PostgresServerVersionError -> IO (Maybe Double)
forall a b. (a -> b) -> a -> b
$ String -> PostgresServerVersionError
PostgresServerVersionError String
err

getServerVersionNonEmpty :: PG.Connection -> IO (NonEmpty Word)
getServerVersionNonEmpty :: Connection -> IO (NonEmpty Word)
getServerVersionNonEmpty Connection
conn = do
  [PG.Only String
version] <- Connection -> Query -> IO [Only String]
forall r. FromRow r => Connection -> Query -> IO [r]
PG.query_ Connection
conn Query
"show server_version";
  case Parser [Word] -> Text -> Either String [Word]
forall a. Parser a -> Text -> Either String a
AT.parseOnly Parser [Word]
parseVersion (String -> Text
T.pack String
version) of
    Left String
err -> PostgresServerVersionError -> IO (NonEmpty Word)
forall e a. Exception e => e -> IO a
throwIO (PostgresServerVersionError -> IO (NonEmpty Word))
-> PostgresServerVersionError -> IO (NonEmpty Word)
forall a b. (a -> b) -> a -> b
$ String -> PostgresServerVersionError
PostgresServerVersionError (String -> PostgresServerVersionError)
-> String -> PostgresServerVersionError
forall a b. (a -> b) -> a -> b
$ String
"Parse failure on: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
version String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
". Error: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
err
    Right [Word]
versionComponents -> case [Word] -> Maybe (NonEmpty Word)
forall a. [a] -> Maybe (NonEmpty a)
NEL.nonEmpty [Word]
versionComponents of
      Maybe (NonEmpty Word)
Nothing -> PostgresServerVersionError -> IO (NonEmpty Word)
forall e a. Exception e => e -> IO a
throwIO (PostgresServerVersionError -> IO (NonEmpty Word))
-> PostgresServerVersionError -> IO (NonEmpty Word)
forall a b. (a -> b) -> a -> b
$ String -> PostgresServerVersionError
PostgresServerVersionError (String -> PostgresServerVersionError)
-> String -> PostgresServerVersionError
forall a b. (a -> b) -> a -> b
$ String
"Empty Postgres version string: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
version
      Just NonEmpty Word
neVersion -> NonEmpty Word -> IO (NonEmpty Word)
forall (f :: * -> *) a. Applicative f => a -> f a
pure NonEmpty Word
neVersion

  where
    -- Partially copied from the `versions` package
    -- Typically server_version gives e.g. 12.3
    -- In Persistent's CI, we get "12.4 (Debian 12.4-1.pgdg100+1)", so we ignore the trailing data.
    parseVersion :: Parser [Word]
parseVersion = Parser Word
forall a. Integral a => Parser a
AT.decimal Parser Word -> Parser Text Char -> Parser [Word]
forall (f :: * -> *) a s. Alternative f => f a -> f s -> f [a]
`AT.sepBy` Char -> Parser Text Char
AT.char Char
'.'

-- | Choose upsert sql generation function based on postgresql version.
-- PostgreSQL version >= 9.5 supports native upsert feature,
-- so depending upon that we have to choose how the sql query is generated.
-- upsertFunction :: Double -> Maybe (EntityDef -> Text -> Text)
upsertFunction :: a -> NonEmpty Word -> Maybe a
upsertFunction :: a -> NonEmpty Word -> Maybe a
upsertFunction a
f NonEmpty Word
version = if (NonEmpty Word
version NonEmpty Word -> NonEmpty Word -> Bool
forall a. Ord a => a -> a -> Bool
>= NonEmpty Word
postgres9dot5)
                         then a -> Maybe a
forall a. a -> Maybe a
Just a
f
                         else Maybe a
forall a. Maybe a
Nothing
  where

postgres9dot5 :: NonEmpty Word
postgres9dot5 :: NonEmpty Word
postgres9dot5 = Word
9 Word -> [Word] -> NonEmpty Word
forall a. a -> [a] -> NonEmpty a
NEL.:| [Word
5]

-- | If the user doesn't supply a Postgres version, we assume this version.
--
-- This is currently below any version-specific features Persistent uses.
minimumPostgresVersion :: NonEmpty Word
minimumPostgresVersion :: NonEmpty Word
minimumPostgresVersion = Word
9 Word -> [Word] -> NonEmpty Word
forall a. a -> [a] -> NonEmpty a
NEL.:| [Word
4]

oldGetVersionToNew :: (PG.Connection -> IO (Maybe Double)) -> (PG.Connection -> IO (NonEmpty Word))
oldGetVersionToNew :: (Connection -> IO (Maybe Double))
-> Connection -> IO (NonEmpty Word)
oldGetVersionToNew Connection -> IO (Maybe Double)
oldFn = \Connection
conn -> do
  Maybe Double
mDouble <- Connection -> IO (Maybe Double)
oldFn Connection
conn
  case Maybe Double
mDouble of
    Maybe Double
Nothing -> NonEmpty Word -> IO (NonEmpty Word)
forall (f :: * -> *) a. Applicative f => a -> f a
pure NonEmpty Word
minimumPostgresVersion
    Just Double
double -> do
      let (Word
major, Double
minor) = Double -> (Word, Double)
forall a b. (RealFrac a, Integral b) => a -> (b, a)
properFraction Double
double
      NonEmpty Word -> IO (NonEmpty Word)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (NonEmpty Word -> IO (NonEmpty Word))
-> NonEmpty Word -> IO (NonEmpty Word)
forall a b. (a -> b) -> a -> b
$ Word
major Word -> [Word] -> NonEmpty Word
forall a. a -> [a] -> NonEmpty a
NEL.:| [Double -> Word
forall a b. (RealFrac a, Integral b) => a -> b
floor Double
minor]

-- | Generate a 'SqlBackend' from a 'PG.Connection'.
openSimpleConn :: LogFunc -> PG.Connection -> IO SqlBackend
openSimpleConn :: LogFunc -> Connection -> IO SqlBackend
openSimpleConn = (Connection -> IO (Maybe Double))
-> LogFunc -> Connection -> IO SqlBackend
openSimpleConnWithVersion Connection -> IO (Maybe Double)
getServerVersion

-- | Generate a 'SqlBackend' from a 'PG.Connection', but takes a callback for
-- obtaining the server version.
--
-- @since 2.9.1
openSimpleConnWithVersion :: (PG.Connection -> IO (Maybe Double)) -> LogFunc -> PG.Connection -> IO SqlBackend
openSimpleConnWithVersion :: (Connection -> IO (Maybe Double))
-> LogFunc -> Connection -> IO SqlBackend
openSimpleConnWithVersion Connection -> IO (Maybe Double)
getVerDouble LogFunc
logFunc Connection
conn = do
    IORef (Map Text Statement)
smap <- Map Text Statement -> IO (IORef (Map Text Statement))
forall a. a -> IO (IORef a)
newIORef Map Text Statement
forall a. Monoid a => a
mempty
    NonEmpty Word
serverVersion <- (Connection -> IO (Maybe Double))
-> Connection -> IO (NonEmpty Word)
oldGetVersionToNew Connection -> IO (Maybe Double)
getVerDouble Connection
conn
    SqlBackend -> IO SqlBackend
forall (m :: * -> *) a. Monad m => a -> m a
return (SqlBackend -> IO SqlBackend) -> SqlBackend -> IO SqlBackend
forall a b. (a -> b) -> a -> b
$ LogFunc
-> NonEmpty Word
-> IORef (Map Text Statement)
-> Connection
-> SqlBackend
createBackend LogFunc
logFunc NonEmpty Word
serverVersion IORef (Map Text Statement)
smap Connection
conn

underlyingConnectionKey :: Vault.Key PG.Connection
underlyingConnectionKey :: Key Connection
underlyingConnectionKey = IO (Key Connection) -> Key Connection
forall a. IO a -> a
unsafePerformIO IO (Key Connection)
forall a. IO (Key a)
Vault.newKey
{-# NOINLINE underlyingConnectionKey #-}

-- | Access underlying connection, returning 'Nothing' if the 'SqlBackend'
-- provided isn't backed by postgresql-simple.
--
-- @since 2.13.0
getSimpleConn :: (BackendCompatible SqlBackend backend) => backend -> Maybe PG.Connection
getSimpleConn :: backend -> Maybe Connection
getSimpleConn = Key Connection -> Vault -> Maybe Connection
forall a. Key a -> Vault -> Maybe a
Vault.lookup Key Connection
underlyingConnectionKey (Vault -> Maybe Connection)
-> (backend -> Vault) -> backend -> Maybe Connection
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> backend -> Vault
forall backend (m :: * -> *).
(BackendCompatible SqlBackend backend, MonadReader backend m) =>
m Vault
getConnVault

-- | Create the backend given a logging function, server version, mutable statement cell,
-- and connection.
createBackend :: LogFunc -> NonEmpty Word
              -> IORef (Map.Map Text Statement) -> PG.Connection -> SqlBackend
createBackend :: LogFunc
-> NonEmpty Word
-> IORef (Map Text Statement)
-> Connection
-> SqlBackend
createBackend LogFunc
logFunc NonEmpty Word
serverVersion IORef (Map Text Statement)
smap Connection
conn =
    (SqlBackend -> SqlBackend)
-> ((EntityDef -> Int -> Text) -> SqlBackend -> SqlBackend)
-> Maybe (EntityDef -> Int -> Text)
-> SqlBackend
-> SqlBackend
forall b a. b -> (a -> b) -> Maybe a -> b
maybe SqlBackend -> SqlBackend
forall a. a -> a
id (EntityDef -> Int -> Text) -> SqlBackend -> SqlBackend
setConnPutManySql ((EntityDef -> Int -> Text)
-> NonEmpty Word -> Maybe (EntityDef -> Int -> Text)
forall a. a -> NonEmpty Word -> Maybe a
upsertFunction EntityDef -> Int -> Text
putManySql NonEmpty Word
serverVersion) (SqlBackend -> SqlBackend) -> SqlBackend -> SqlBackend
forall a b. (a -> b) -> a -> b
$
    (SqlBackend -> SqlBackend)
-> ((EntityDef
     -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)
    -> SqlBackend -> SqlBackend)
-> Maybe
     (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)
-> SqlBackend
-> SqlBackend
forall b a. b -> (a -> b) -> Maybe a -> b
maybe SqlBackend -> SqlBackend
forall a. a -> a
id (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)
-> SqlBackend -> SqlBackend
setConnUpsertSql ((EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)
-> NonEmpty Word
-> Maybe
     (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)
forall a. a -> NonEmpty Word -> Maybe a
upsertFunction EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text
upsertSql' NonEmpty Word
serverVersion) (SqlBackend -> SqlBackend) -> SqlBackend -> SqlBackend
forall a b. (a -> b) -> a -> b
$
    (EntityDef -> [[PersistValue]] -> InsertSqlResult)
-> SqlBackend -> SqlBackend
setConnInsertManySql EntityDef -> [[PersistValue]] -> InsertSqlResult
insertManySql' (SqlBackend -> SqlBackend) -> SqlBackend -> SqlBackend
forall a b. (a -> b) -> a -> b
$
    (SqlBackend -> SqlBackend)
-> ((EntityDef -> Int -> Text) -> SqlBackend -> SqlBackend)
-> Maybe (EntityDef -> Int -> Text)
-> SqlBackend
-> SqlBackend
forall b a. b -> (a -> b) -> Maybe a -> b
maybe SqlBackend -> SqlBackend
forall a. a -> a
id (EntityDef -> Int -> Text) -> SqlBackend -> SqlBackend
setConnRepsertManySql ((EntityDef -> Int -> Text)
-> NonEmpty Word -> Maybe (EntityDef -> Int -> Text)
forall a. a -> NonEmpty Word -> Maybe a
upsertFunction EntityDef -> Int -> Text
repsertManySql NonEmpty Word
serverVersion) (SqlBackend -> SqlBackend) -> SqlBackend -> SqlBackend
forall a b. (a -> b) -> a -> b
$
    (Vault -> Vault) -> SqlBackend -> SqlBackend
modifyConnVault (Key Connection -> Connection -> Vault -> Vault
forall a. Key a -> a -> Vault -> Vault
Vault.insert Key Connection
underlyingConnectionKey Connection
conn) (SqlBackend -> SqlBackend) -> SqlBackend -> SqlBackend
forall a b. (a -> b) -> a -> b
$ MkSqlBackendArgs -> SqlBackend
mkSqlBackend MkSqlBackendArgs :: (Text -> IO Statement)
-> (EntityDef -> [PersistValue] -> InsertSqlResult)
-> IORef (Map Text Statement)
-> IO ()
-> ([EntityDef]
    -> (Text -> IO Statement)
    -> EntityDef
    -> IO (Either [Text] [(Bool, Text)]))
-> ((Text -> IO Statement) -> Maybe IsolationLevel -> IO ())
-> ((Text -> IO Statement) -> IO ())
-> ((Text -> IO Statement) -> IO ())
-> (FieldNameDB -> Text)
-> (EntityDef -> Text)
-> (Text -> Text)
-> Text
-> Text
-> ((Int, Int) -> Text -> Text)
-> LogFunc
-> MkSqlBackendArgs
MkSqlBackendArgs
        { connPrepare :: Text -> IO Statement
connPrepare    = Connection -> Text -> IO Statement
prepare' Connection
conn
        , connStmtMap :: IORef (Map Text Statement)
connStmtMap    = IORef (Map Text Statement)
smap
        , connInsertSql :: EntityDef -> [PersistValue] -> InsertSqlResult
connInsertSql  = EntityDef -> [PersistValue] -> InsertSqlResult
insertSql'
        , connClose :: IO ()
connClose      = Connection -> IO ()
PG.close Connection
conn
        , connMigrateSql :: [EntityDef]
-> (Text -> IO Statement)
-> EntityDef
-> IO (Either [Text] [(Bool, Text)])
connMigrateSql = [EntityDef]
-> (Text -> IO Statement)
-> EntityDef
-> IO (Either [Text] [(Bool, Text)])
migrate'
        , connBegin :: (Text -> IO Statement) -> Maybe IsolationLevel -> IO ()
connBegin      = \Text -> IO Statement
_ Maybe IsolationLevel
mIsolation -> case Maybe IsolationLevel
mIsolation of
              Maybe IsolationLevel
Nothing -> Connection -> IO ()
PG.begin Connection
conn
              Just IsolationLevel
iso -> IsolationLevel -> Connection -> IO ()
PG.beginLevel (case IsolationLevel
iso of
                  IsolationLevel
ReadUncommitted -> IsolationLevel
PG.ReadCommitted -- PG Upgrades uncommitted reads to committed anyways
                  IsolationLevel
ReadCommitted -> IsolationLevel
PG.ReadCommitted
                  IsolationLevel
RepeatableRead -> IsolationLevel
PG.RepeatableRead
                  IsolationLevel
Serializable -> IsolationLevel
PG.Serializable) Connection
conn
        , connCommit :: (Text -> IO Statement) -> IO ()
connCommit     = IO () -> (Text -> IO Statement) -> IO ()
forall a b. a -> b -> a
const (IO () -> (Text -> IO Statement) -> IO ())
-> IO () -> (Text -> IO Statement) -> IO ()
forall a b. (a -> b) -> a -> b
$ Connection -> IO ()
PG.commit   Connection
conn
        , connRollback :: (Text -> IO Statement) -> IO ()
connRollback   = IO () -> (Text -> IO Statement) -> IO ()
forall a b. a -> b -> a
const (IO () -> (Text -> IO Statement) -> IO ())
-> IO () -> (Text -> IO Statement) -> IO ()
forall a b. (a -> b) -> a -> b
$ Connection -> IO ()
PG.rollback Connection
conn
        , connEscapeFieldName :: FieldNameDB -> Text
connEscapeFieldName = FieldNameDB -> Text
escapeF
        , connEscapeTableName :: EntityDef -> Text
connEscapeTableName = EntityNameDB -> Text
escapeE (EntityNameDB -> Text)
-> (EntityDef -> EntityNameDB) -> EntityDef -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntityDef -> EntityNameDB
getEntityDBName
        , connEscapeRawName :: Text -> Text
connEscapeRawName = Text -> Text
escape
        , connNoLimit :: Text
connNoLimit    = Text
"LIMIT ALL"
        , connRDBMS :: Text
connRDBMS      = Text
"postgresql"
        , connLimitOffset :: (Int, Int) -> Text -> Text
connLimitOffset = Text -> (Int, Int) -> Text -> Text
decorateSQLWithLimitOffset Text
"LIMIT ALL"
        , connLogFunc :: LogFunc
connLogFunc = LogFunc
logFunc
        }

prepare' :: PG.Connection -> Text -> IO Statement
prepare' :: Connection -> Text -> IO Statement
prepare' Connection
conn Text
sql = do
    let query :: Query
query = ConnectionString -> Query
PG.Query (Text -> ConnectionString
T.encodeUtf8 Text
sql)
    Statement -> IO Statement
forall (m :: * -> *) a. Monad m => a -> m a
return Statement :: IO ()
-> IO ()
-> ([PersistValue] -> IO Int64)
-> (forall (m :: * -> *).
    MonadIO m =>
    [PersistValue] -> Acquire (ConduitM () [PersistValue] m ()))
-> Statement
Statement
        { stmtFinalize :: IO ()
stmtFinalize = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        , stmtReset :: IO ()
stmtReset = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        , stmtExecute :: [PersistValue] -> IO Int64
stmtExecute = Connection -> Query -> [PersistValue] -> IO Int64
execute' Connection
conn Query
query
        , stmtQuery :: forall (m :: * -> *).
MonadIO m =>
[PersistValue] -> Acquire (ConduitM () [PersistValue] m ())
stmtQuery = Connection
-> Query
-> [PersistValue]
-> Acquire (ConduitM () [PersistValue] m ())
forall (m :: * -> *).
MonadIO m =>
Connection
-> Query
-> [PersistValue]
-> Acquire (ConduitM () [PersistValue] m ())
withStmt' Connection
conn Query
query
        }

insertSql' :: EntityDef -> [PersistValue] -> InsertSqlResult
insertSql' :: EntityDef -> [PersistValue] -> InsertSqlResult
insertSql' EntityDef
ent [PersistValue]
vals =
    case EntityDef -> EntityIdDef
getEntityId EntityDef
ent of
        EntityIdNaturalKey CompositeDef
_pdef ->
            Text -> [PersistValue] -> InsertSqlResult
ISRManyKeys Text
sql [PersistValue]
vals
        EntityIdField FieldDef
field ->
            Text -> InsertSqlResult
ISRSingle (Text
sql Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" RETURNING " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FieldNameDB -> Text
escapeF (FieldDef -> FieldNameDB
fieldDB FieldDef
field))
  where
    ([Text]
fieldNames, [Text]
placeholders) = [(Text, Text)] -> ([Text], [Text])
forall a b. [(a, b)] -> ([a], [b])
unzip (EntityDef -> (FieldNameDB -> Text) -> [(Text, Text)]
Util.mkInsertPlaceholders EntityDef
ent FieldNameDB -> Text
escapeF)
    sql :: Text
sql = [Text] -> Text
T.concat
        [ Text
"INSERT INTO "
        , EntityNameDB -> Text
escapeE (EntityNameDB -> Text) -> EntityNameDB -> Text
forall a b. (a -> b) -> a -> b
$ EntityDef -> EntityNameDB
getEntityDBName EntityDef
ent
        , if [FieldDef] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (EntityDef -> [FieldDef]
getEntityFields EntityDef
ent)
            then Text
" DEFAULT VALUES"
            else [Text] -> Text
T.concat
                [ Text
"("
                , Text -> [Text] -> Text
T.intercalate Text
"," [Text]
fieldNames
                , Text
") VALUES("
                , Text -> [Text] -> Text
T.intercalate Text
"," [Text]
placeholders
                , Text
")"
                ]
        ]

upsertSql' :: EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text
upsertSql' :: EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text
upsertSql' EntityDef
ent NonEmpty (FieldNameHS, FieldNameDB)
uniqs Text
updateVal =
    [Text] -> Text
T.concat
        [ Text
"INSERT INTO "
        , EntityNameDB -> Text
escapeE (EntityDef -> EntityNameDB
getEntityDBName EntityDef
ent)
        , Text
"("
        , Text -> [Text] -> Text
T.intercalate Text
"," [Text]
fieldNames
        , Text
") VALUES ("
        , Text -> [Text] -> Text
T.intercalate Text
"," [Text]
placeholders
        , Text
") ON CONFLICT ("
        , Text -> [Text] -> Text
T.intercalate Text
"," ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ ((FieldNameHS, FieldNameDB) -> Text)
-> [(FieldNameHS, FieldNameDB)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (FieldNameDB -> Text
escapeF (FieldNameDB -> Text)
-> ((FieldNameHS, FieldNameDB) -> FieldNameDB)
-> (FieldNameHS, FieldNameDB)
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FieldNameHS, FieldNameDB) -> FieldNameDB
forall a b. (a, b) -> b
snd) (NonEmpty (FieldNameHS, FieldNameDB) -> [(FieldNameHS, FieldNameDB)]
forall a. NonEmpty a -> [a]
NEL.toList NonEmpty (FieldNameHS, FieldNameDB)
uniqs)
        , Text
") DO UPDATE SET "
        , Text
updateVal
        , Text
" WHERE "
        , Text
wher
        , Text
" RETURNING ??"
        ]
  where
    ([Text]
fieldNames, [Text]
placeholders) = [(Text, Text)] -> ([Text], [Text])
forall a b. [(a, b)] -> ([a], [b])
unzip (EntityDef -> (FieldNameDB -> Text) -> [(Text, Text)]
Util.mkInsertPlaceholders EntityDef
ent FieldNameDB -> Text
escapeF)

    wher :: Text
wher = Text -> [Text] -> Text
T.intercalate Text
" AND " ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ ((FieldNameHS, FieldNameDB) -> Text)
-> [(FieldNameHS, FieldNameDB)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (FieldNameDB -> Text
singleClause (FieldNameDB -> Text)
-> ((FieldNameHS, FieldNameDB) -> FieldNameDB)
-> (FieldNameHS, FieldNameDB)
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FieldNameHS, FieldNameDB) -> FieldNameDB
forall a b. (a, b) -> b
snd) ([(FieldNameHS, FieldNameDB)] -> [Text])
-> [(FieldNameHS, FieldNameDB)] -> [Text]
forall a b. (a -> b) -> a -> b
$ NonEmpty (FieldNameHS, FieldNameDB) -> [(FieldNameHS, FieldNameDB)]
forall a. NonEmpty a -> [a]
NEL.toList NonEmpty (FieldNameHS, FieldNameDB)
uniqs

    singleClause :: FieldNameDB -> Text
    singleClause :: FieldNameDB -> Text
singleClause FieldNameDB
field = EntityNameDB -> Text
escapeE (EntityDef -> EntityNameDB
getEntityDBName EntityDef
ent) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (FieldNameDB -> Text
escapeF FieldNameDB
field) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" =?"

-- | SQL for inserting multiple rows at once and returning their primary keys.
insertManySql' :: EntityDef -> [[PersistValue]] -> InsertSqlResult
insertManySql' :: EntityDef -> [[PersistValue]] -> InsertSqlResult
insertManySql' EntityDef
ent [[PersistValue]]
valss =
    Text -> InsertSqlResult
ISRSingle Text
sql
  where
    ([Text]
fieldNames, [Text]
placeholders)= [(Text, Text)] -> ([Text], [Text])
forall a b. [(a, b)] -> ([a], [b])
unzip (EntityDef -> (FieldNameDB -> Text) -> [(Text, Text)]
Util.mkInsertPlaceholders EntityDef
ent FieldNameDB -> Text
escapeF)
    sql :: Text
sql = [Text] -> Text
T.concat
        [ Text
"INSERT INTO "
        , EntityNameDB -> Text
escapeE (EntityDef -> EntityNameDB
getEntityDBName EntityDef
ent)
        , Text
"("
        , Text -> [Text] -> Text
T.intercalate Text
"," [Text]
fieldNames
        , Text
") VALUES ("
        , Text -> [Text] -> Text
T.intercalate Text
"),(" ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text -> [Text]
forall a. Int -> a -> [a]
replicate ([[PersistValue]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[PersistValue]]
valss) (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> Text
T.intercalate Text
"," [Text]
placeholders
        , Text
") RETURNING "
        , [Text] -> Text
Util.commaSeparated ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ NonEmpty Text -> [Text]
forall a. NonEmpty a -> [a]
NEL.toList (NonEmpty Text -> [Text]) -> NonEmpty Text -> [Text]
forall a b. (a -> b) -> a -> b
$ (FieldNameDB -> Text) -> EntityDef -> NonEmpty Text
Util.dbIdColumnsEsc FieldNameDB -> Text
escapeF EntityDef
ent
        ]


execute' :: PG.Connection -> PG.Query -> [PersistValue] -> IO Int64
execute' :: Connection -> Query -> [PersistValue] -> IO Int64
execute' Connection
conn Query
query [PersistValue]
vals = Connection -> Query -> [P] -> IO Int64
forall q. ToRow q => Connection -> Query -> q -> IO Int64
PG.execute Connection
conn Query
query ((PersistValue -> P) -> [PersistValue] -> [P]
forall a b. (a -> b) -> [a] -> [b]
map PersistValue -> P
P [PersistValue]
vals)

withStmt' :: MonadIO m
          => PG.Connection
          -> PG.Query
          -> [PersistValue]
          -> Acquire (ConduitM () [PersistValue] m ())
withStmt' :: Connection
-> Query
-> [PersistValue]
-> Acquire (ConduitM () [PersistValue] m ())
withStmt' Connection
conn Query
query [PersistValue]
vals =
    (Result, IORef Row, Row,
 [Maybe ConnectionString -> Conversion PersistValue])
-> ConduitM () [PersistValue] m ()
pull ((Result, IORef Row, Row,
  [Maybe ConnectionString -> Conversion PersistValue])
 -> ConduitM () [PersistValue] m ())
-> Acquire
     (Result, IORef Row, Row,
      [Maybe ConnectionString -> Conversion PersistValue])
-> Acquire (ConduitM () [PersistValue] m ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` IO
  (Result, IORef Row, Row,
   [Maybe ConnectionString -> Conversion PersistValue])
-> ((Result, IORef Row, Row,
     [Maybe ConnectionString -> Conversion PersistValue])
    -> IO ())
-> Acquire
     (Result, IORef Row, Row,
      [Maybe ConnectionString -> Conversion PersistValue])
forall a. IO a -> (a -> IO ()) -> Acquire a
mkAcquire IO
  (Result, IORef Row, Row,
   [Maybe ConnectionString -> Conversion PersistValue])
openS (Result, IORef Row, Row,
 [Maybe ConnectionString -> Conversion PersistValue])
-> IO ()
forall b c d. (Result, b, c, d) -> IO ()
closeS
  where
    openS :: IO
  (Result, IORef Row, Row,
   [Maybe ConnectionString -> Conversion PersistValue])
openS = do
      -- Construct raw query
      ConnectionString
rawquery <- Connection -> Query -> [P] -> IO ConnectionString
forall q.
ToRow q =>
Connection -> Query -> q -> IO ConnectionString
PG.formatQuery Connection
conn Query
query ((PersistValue -> P) -> [PersistValue] -> [P]
forall a b. (a -> b) -> [a] -> [b]
map PersistValue -> P
P [PersistValue]
vals)

      -- Take raw connection
      (Result
rt, IORef Row
rr, Row
rc, [(Column, Oid)]
ids) <- Connection
-> (Connection -> IO (Result, IORef Row, Row, [(Column, Oid)]))
-> IO (Result, IORef Row, Row, [(Column, Oid)])
forall a. Connection -> (Connection -> IO a) -> IO a
PG.withConnection Connection
conn ((Connection -> IO (Result, IORef Row, Row, [(Column, Oid)]))
 -> IO (Result, IORef Row, Row, [(Column, Oid)]))
-> (Connection -> IO (Result, IORef Row, Row, [(Column, Oid)]))
-> IO (Result, IORef Row, Row, [(Column, Oid)])
forall a b. (a -> b) -> a -> b
$ \Connection
rawconn -> do
            -- Execute query
            Maybe Result
mret <- Connection -> ConnectionString -> IO (Maybe Result)
LibPQ.exec Connection
rawconn ConnectionString
rawquery
            case Maybe Result
mret of
              Maybe Result
Nothing -> do
                Maybe ConnectionString
merr <- Connection -> IO (Maybe ConnectionString)
LibPQ.errorMessage Connection
rawconn
                String -> IO (Result, IORef Row, Row, [(Column, Oid)])
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> IO (Result, IORef Row, Row, [(Column, Oid)]))
-> String -> IO (Result, IORef Row, Row, [(Column, Oid)])
forall a b. (a -> b) -> a -> b
$ case Maybe ConnectionString
merr of
                         Maybe ConnectionString
Nothing -> String
"Postgresql.withStmt': unknown error"
                         Just ConnectionString
e  -> String
"Postgresql.withStmt': " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ConnectionString -> String
B8.unpack ConnectionString
e
              Just Result
ret -> do
                -- Check result status
                ExecStatus
status <- Result -> IO ExecStatus
LibPQ.resultStatus Result
ret
                case ExecStatus
status of
                  ExecStatus
LibPQ.TuplesOk -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
                  ExecStatus
_ -> ConnectionString -> Result -> ExecStatus -> IO ()
forall a. ConnectionString -> Result -> ExecStatus -> IO a
PG.throwResultError ConnectionString
"Postgresql.withStmt': bad result status " Result
ret ExecStatus
status

                -- Get number and type of columns
                Column
cols <- Result -> IO Column
LibPQ.nfields Result
ret
                [(Column, Oid)]
oids <- [Column] -> (Column -> IO (Column, Oid)) -> IO [(Column, Oid)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Column
0..Column
colsColumn -> Column -> Column
forall a. Num a => a -> a -> a
-Column
1] ((Column -> IO (Column, Oid)) -> IO [(Column, Oid)])
-> (Column -> IO (Column, Oid)) -> IO [(Column, Oid)]
forall a b. (a -> b) -> a -> b
$ \Column
col -> (Oid -> (Column, Oid)) -> IO Oid -> IO (Column, Oid)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((,) Column
col) (Result -> Column -> IO Oid
LibPQ.ftype Result
ret Column
col)
                -- Ready to go!
                IORef Row
rowRef   <- Row -> IO (IORef Row)
forall a. a -> IO (IORef a)
newIORef (CInt -> Row
LibPQ.Row CInt
0)
                Row
rowCount <- Result -> IO Row
LibPQ.ntuples Result
ret
                (Result, IORef Row, Row, [(Column, Oid)])
-> IO (Result, IORef Row, Row, [(Column, Oid)])
forall (m :: * -> *) a. Monad m => a -> m a
return (Result
ret, IORef Row
rowRef, Row
rowCount, [(Column, Oid)]
oids)
      let getters :: [Maybe ConnectionString -> Conversion PersistValue]
getters
            = ((Column, Oid)
 -> Maybe ConnectionString -> Conversion PersistValue)
-> [(Column, Oid)]
-> [Maybe ConnectionString -> Conversion PersistValue]
forall a b. (a -> b) -> [a] -> [b]
map (\(Column
col, Oid
oid) -> Oid -> Getter PersistValue
getGetter Oid
oid Getter PersistValue -> Getter PersistValue
forall a b. (a -> b) -> a -> b
$ Result -> Column -> Oid -> Field
PG.Field Result
rt Column
col Oid
oid) [(Column, Oid)]
ids
      (Result, IORef Row, Row,
 [Maybe ConnectionString -> Conversion PersistValue])
-> IO
     (Result, IORef Row, Row,
      [Maybe ConnectionString -> Conversion PersistValue])
forall (m :: * -> *) a. Monad m => a -> m a
return (Result
rt, IORef Row
rr, Row
rc, [Maybe ConnectionString -> Conversion PersistValue]
getters)

    closeS :: (Result, b, c, d) -> IO ()
closeS (Result
ret, b
_, c
_, d
_) = Result -> IO ()
LibPQ.unsafeFreeResult Result
ret

    pull :: (Result, IORef Row, Row,
 [Maybe ConnectionString -> Conversion PersistValue])
-> ConduitM () [PersistValue] m ()
pull (Result, IORef Row, Row,
 [Maybe ConnectionString -> Conversion PersistValue])
x = do
        Maybe [PersistValue]
y <- IO (Maybe [PersistValue])
-> ConduitT () [PersistValue] m (Maybe [PersistValue])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [PersistValue])
 -> ConduitT () [PersistValue] m (Maybe [PersistValue]))
-> IO (Maybe [PersistValue])
-> ConduitT () [PersistValue] m (Maybe [PersistValue])
forall a b. (a -> b) -> a -> b
$ (Result, IORef Row, Row,
 [Maybe ConnectionString -> Conversion PersistValue])
-> IO (Maybe [PersistValue])
pullS (Result, IORef Row, Row,
 [Maybe ConnectionString -> Conversion PersistValue])
x
        case Maybe [PersistValue]
y of
            Maybe [PersistValue]
Nothing -> () -> ConduitM () [PersistValue] m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
            Just [PersistValue]
z -> [PersistValue] -> ConduitM () [PersistValue] m ()
forall (m :: * -> *) o i. Monad m => o -> ConduitT i o m ()
yield [PersistValue]
z ConduitM () [PersistValue] m ()
-> ConduitM () [PersistValue] m ()
-> ConduitM () [PersistValue] m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (Result, IORef Row, Row,
 [Maybe ConnectionString -> Conversion PersistValue])
-> ConduitM () [PersistValue] m ()
pull (Result, IORef Row, Row,
 [Maybe ConnectionString -> Conversion PersistValue])
x

    pullS :: (Result, IORef Row, Row,
 [Maybe ConnectionString -> Conversion PersistValue])
-> IO (Maybe [PersistValue])
pullS (Result
ret, IORef Row
rowRef, Row
rowCount, [Maybe ConnectionString -> Conversion PersistValue]
getters) = do
        Row
row <- IORef Row -> (Row -> (Row, Row)) -> IO Row
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef IORef Row
rowRef (\Row
r -> (Row
rRow -> Row -> Row
forall a. Num a => a -> a -> a
+Row
1, Row
r))
        if Row
row Row -> Row -> Bool
forall a. Eq a => a -> a -> Bool
== Row
rowCount
           then Maybe [PersistValue] -> IO (Maybe [PersistValue])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [PersistValue]
forall a. Maybe a
Nothing
           else ([PersistValue] -> Maybe [PersistValue])
-> IO [PersistValue] -> IO (Maybe [PersistValue])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [PersistValue] -> Maybe [PersistValue]
forall a. a -> Maybe a
Just (IO [PersistValue] -> IO (Maybe [PersistValue]))
-> IO [PersistValue] -> IO (Maybe [PersistValue])
forall a b. (a -> b) -> a -> b
$ [(Maybe ConnectionString -> Conversion PersistValue, Column)]
-> ((Maybe ConnectionString -> Conversion PersistValue, Column)
    -> IO PersistValue)
-> IO [PersistValue]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM ([Maybe ConnectionString -> Conversion PersistValue]
-> [Column]
-> [(Maybe ConnectionString -> Conversion PersistValue, Column)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Maybe ConnectionString -> Conversion PersistValue]
getters [Column
0..]) (((Maybe ConnectionString -> Conversion PersistValue, Column)
  -> IO PersistValue)
 -> IO [PersistValue])
-> ((Maybe ConnectionString -> Conversion PersistValue, Column)
    -> IO PersistValue)
-> IO [PersistValue]
forall a b. (a -> b) -> a -> b
$ \(Maybe ConnectionString -> Conversion PersistValue
getter, Column
col) -> do
                                Maybe ConnectionString
mbs <- Result -> Row -> Column -> IO (Maybe ConnectionString)
LibPQ.getvalue' Result
ret Row
row Column
col
                                case Maybe ConnectionString
mbs of
                                  Maybe ConnectionString
Nothing ->
                                    -- getvalue' verified that the value is NULL.
                                    -- However, that does not mean that there are
                                    -- no NULL values inside the value (e.g., if
                                    -- we're dealing with an array of optional values).
                                    PersistValue -> IO PersistValue
forall (m :: * -> *) a. Monad m => a -> m a
return PersistValue
PersistNull
                                  Just ConnectionString
bs -> do
                                    Ok PersistValue
ok <- Conversion PersistValue -> Connection -> IO (Ok PersistValue)
forall a. Conversion a -> Connection -> IO (Ok a)
PGFF.runConversion (Maybe ConnectionString -> Conversion PersistValue
getter Maybe ConnectionString
mbs) Connection
conn
                                    ConnectionString
bs ConnectionString -> IO PersistValue -> IO PersistValue
`seq` case Ok PersistValue
ok of
                                                        Errors (SomeException
exc:[SomeException]
_) -> SomeException -> IO PersistValue
forall a e. Exception e => e -> a
throw SomeException
exc
                                                        Errors [] -> String -> IO PersistValue
forall a. HasCallStack => String -> a
error String
"Got an Errors, but no exceptions"
                                                        Ok PersistValue
v  -> PersistValue -> IO PersistValue
forall (m :: * -> *) a. Monad m => a -> m a
return PersistValue
v

doesTableExist :: (Text -> IO Statement)
               -> EntityNameDB
               -> IO Bool
doesTableExist :: (Text -> IO Statement) -> EntityNameDB -> IO Bool
doesTableExist Text -> IO Statement
getter (EntityNameDB Text
name) = do
    Statement
stmt <- Text -> IO Statement
getter Text
sql
    Acquire (ConduitM () [PersistValue] IO ())
-> (ConduitM () [PersistValue] IO () -> IO Bool) -> IO Bool
forall (m :: * -> *) a b.
MonadUnliftIO m =>
Acquire a -> (a -> m b) -> m b
with (Statement
-> [PersistValue] -> Acquire (ConduitM () [PersistValue] IO ())
Statement
-> forall (m :: * -> *).
   MonadIO m =>
   [PersistValue] -> Acquire (ConduitM () [PersistValue] m ())
stmtQuery Statement
stmt [PersistValue]
vals) (\ConduitM () [PersistValue] IO ()
src -> ConduitT () Void IO Bool -> IO Bool
forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit (ConduitT () Void IO Bool -> IO Bool)
-> ConduitT () Void IO Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ ConduitM () [PersistValue] IO ()
src ConduitM () [PersistValue] IO ()
-> ConduitM [PersistValue] Void IO Bool -> ConduitT () Void IO Bool
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.| ConduitM [PersistValue] Void IO Bool
forall o. ConduitT [PersistValue] o IO Bool
start)
  where
    sql :: Text
sql = Text
"SELECT COUNT(*) FROM pg_catalog.pg_tables WHERE schemaname != 'pg_catalog'"
          Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" AND schemaname != 'information_schema' AND tablename=?"
    vals :: [PersistValue]
vals = [Text -> PersistValue
PersistText Text
name]

    start :: ConduitT [PersistValue] o IO Bool
start = ConduitT [PersistValue] o IO (Maybe [PersistValue])
forall (m :: * -> *) i. Monad m => Consumer i m (Maybe i)
await ConduitT [PersistValue] o IO (Maybe [PersistValue])
-> (Maybe [PersistValue] -> ConduitT [PersistValue] o IO Bool)
-> ConduitT [PersistValue] o IO Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ConduitT [PersistValue] o IO Bool
-> ([PersistValue] -> ConduitT [PersistValue] o IO Bool)
-> Maybe [PersistValue]
-> ConduitT [PersistValue] o IO Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> ConduitT [PersistValue] o IO Bool
forall a. HasCallStack => String -> a
error String
"No results when checking doesTableExist") [PersistValue] -> ConduitT [PersistValue] o IO Bool
forall (m :: * -> *) a o.
Monad m =>
[PersistValue] -> ConduitT a o m Bool
start'
    start' :: [PersistValue] -> ConduitT a o m Bool
start' [PersistInt64 Int64
0] = Bool -> ConduitT a o m Bool
forall (m :: * -> *) b a o. Monad m => b -> ConduitT a o m b
finish Bool
False
    start' [PersistInt64 Int64
1] = Bool -> ConduitT a o m Bool
forall (m :: * -> *) b a o. Monad m => b -> ConduitT a o m b
finish Bool
True
    start' [PersistValue]
res = String -> ConduitT a o m Bool
forall a. HasCallStack => String -> a
error (String -> ConduitT a o m Bool) -> String -> ConduitT a o m Bool
forall a b. (a -> b) -> a -> b
$ String
"doesTableExist returned unexpected result: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [PersistValue] -> String
forall a. Show a => a -> String
show [PersistValue]
res
    finish :: b -> ConduitT a o m b
finish b
x = ConduitT a o m (Maybe a)
forall (m :: * -> *) i. Monad m => Consumer i m (Maybe i)
await ConduitT a o m (Maybe a)
-> (Maybe a -> ConduitT a o m b) -> ConduitT a o m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ConduitT a o m b
-> (a -> ConduitT a o m b) -> Maybe a -> ConduitT a o m b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (b -> ConduitT a o m b
forall (m :: * -> *) a. Monad m => a -> m a
return b
x) (String -> a -> ConduitT a o m b
forall a. HasCallStack => String -> a
error String
"Too many rows returned in doesTableExist")

migrate' :: [EntityDef]
         -> (Text -> IO Statement)
         -> EntityDef
         -> IO (Either [Text] [(Bool, Text)])
migrate' :: [EntityDef]
-> (Text -> IO Statement)
-> EntityDef
-> IO (Either [Text] [(Bool, Text)])
migrate' [EntityDef]
allDefs Text -> IO Statement
getter EntityDef
entity = (Either [Text] [AlterDB] -> Either [Text] [(Bool, Text)])
-> IO (Either [Text] [AlterDB])
-> IO (Either [Text] [(Bool, Text)])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([AlterDB] -> [(Bool, Text)])
-> Either [Text] [AlterDB] -> Either [Text] [(Bool, Text)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([AlterDB] -> [(Bool, Text)])
 -> Either [Text] [AlterDB] -> Either [Text] [(Bool, Text)])
-> ([AlterDB] -> [(Bool, Text)])
-> Either [Text] [AlterDB]
-> Either [Text] [(Bool, Text)]
forall a b. (a -> b) -> a -> b
$ (AlterDB -> (Bool, Text)) -> [AlterDB] -> [(Bool, Text)]
forall a b. (a -> b) -> [a] -> [b]
map AlterDB -> (Bool, Text)
showAlterDb) (IO (Either [Text] [AlterDB]) -> IO (Either [Text] [(Bool, Text)]))
-> IO (Either [Text] [AlterDB])
-> IO (Either [Text] [(Bool, Text)])
forall a b. (a -> b) -> a -> b
$ do
    [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
old <- (Text -> IO Statement)
-> EntityDef
-> [Column]
-> IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
getColumns Text -> IO Statement
getter EntityDef
entity [Column]
newcols'
    case [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
-> ([Text], [Either Column (ConstraintNameDB, [FieldNameDB])])
forall a b. [Either a b] -> ([a], [b])
partitionEithers [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
old of
        ([], [Either Column (ConstraintNameDB, [FieldNameDB])]
old'') -> do
            Bool
exists' <-
                if [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
-> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
old
                    then (Text -> IO Statement) -> EntityNameDB -> IO Bool
doesTableExist Text -> IO Statement
getter EntityNameDB
name
                    else Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
            Either [Text] [AlterDB] -> IO (Either [Text] [AlterDB])
forall (m :: * -> *) a. Monad m => a -> m a
return (Either [Text] [AlterDB] -> IO (Either [Text] [AlterDB]))
-> Either [Text] [AlterDB] -> IO (Either [Text] [AlterDB])
forall a b. (a -> b) -> a -> b
$ [AlterDB] -> Either [Text] [AlterDB]
forall a b. b -> Either a b
Right ([AlterDB] -> Either [Text] [AlterDB])
-> [AlterDB] -> Either [Text] [AlterDB]
forall a b. (a -> b) -> a -> b
$ Bool
-> [Either Column (ConstraintNameDB, [FieldNameDB])] -> [AlterDB]
migrationText Bool
exists' [Either Column (ConstraintNameDB, [FieldNameDB])]
old''
        ([Text]
errs, [Either Column (ConstraintNameDB, [FieldNameDB])]
_) -> Either [Text] [AlterDB] -> IO (Either [Text] [AlterDB])
forall (m :: * -> *) a. Monad m => a -> m a
return (Either [Text] [AlterDB] -> IO (Either [Text] [AlterDB]))
-> Either [Text] [AlterDB] -> IO (Either [Text] [AlterDB])
forall a b. (a -> b) -> a -> b
$ [Text] -> Either [Text] [AlterDB]
forall a b. a -> Either a b
Left [Text]
errs
  where
    name :: EntityNameDB
name = EntityDef -> EntityNameDB
getEntityDBName EntityDef
entity
    ([Column]
newcols', [UniqueDef]
udefs, [ForeignDef]
fdefs) = [EntityDef] -> EntityDef -> ([Column], [UniqueDef], [ForeignDef])
postgresMkColumns [EntityDef]
allDefs EntityDef
entity
    migrationText :: Bool
-> [Either Column (ConstraintNameDB, [FieldNameDB])] -> [AlterDB]
migrationText Bool
exists' [Either Column (ConstraintNameDB, [FieldNameDB])]
old''
        | Bool -> Bool
not Bool
exists' =
            [Column]
-> [ForeignDef] -> [(ConstraintNameDB, [FieldNameDB])] -> [AlterDB]
createText [Column]
newcols [ForeignDef]
fdefs [(ConstraintNameDB, [FieldNameDB])]
udspair
        | Bool
otherwise =
            let ([AlterColumn]
acs, [AlterTable]
ats) =
                    [EntityDef]
-> EntityDef
-> ([Column], [(ConstraintNameDB, [FieldNameDB])])
-> ([Column], [(ConstraintNameDB, [FieldNameDB])])
-> ([AlterColumn], [AlterTable])
getAlters [EntityDef]
allDefs EntityDef
entity ([Column]
newcols, [(ConstraintNameDB, [FieldNameDB])]
udspair) ([Column], [(ConstraintNameDB, [FieldNameDB])])
old'
                acs' :: [AlterDB]
acs' = (AlterColumn -> AlterDB) -> [AlterColumn] -> [AlterDB]
forall a b. (a -> b) -> [a] -> [b]
map (EntityNameDB -> AlterColumn -> AlterDB
AlterColumn EntityNameDB
name) [AlterColumn]
acs
                ats' :: [AlterDB]
ats' = (AlterTable -> AlterDB) -> [AlterTable] -> [AlterDB]
forall a b. (a -> b) -> [a] -> [b]
map (EntityNameDB -> AlterTable -> AlterDB
AlterTable EntityNameDB
name) [AlterTable]
ats
            in
                [AlterDB]
acs' [AlterDB] -> [AlterDB] -> [AlterDB]
forall a. [a] -> [a] -> [a]
++ [AlterDB]
ats'
       where
         old' :: ([Column], [(ConstraintNameDB, [FieldNameDB])])
old' = [Either Column (ConstraintNameDB, [FieldNameDB])]
-> ([Column], [(ConstraintNameDB, [FieldNameDB])])
forall a b. [Either a b] -> ([a], [b])
partitionEithers [Either Column (ConstraintNameDB, [FieldNameDB])]
old''
         newcols :: [Column]
newcols = (Column -> Bool) -> [Column] -> [Column]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Column -> Bool) -> Column -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntityDef -> FieldNameDB -> Bool
safeToRemove EntityDef
entity (FieldNameDB -> Bool) -> (Column -> FieldNameDB) -> Column -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Column -> FieldNameDB
cName) [Column]
newcols'
         udspair :: [(ConstraintNameDB, [FieldNameDB])]
udspair = (UniqueDef -> (ConstraintNameDB, [FieldNameDB]))
-> [UniqueDef] -> [(ConstraintNameDB, [FieldNameDB])]
forall a b. (a -> b) -> [a] -> [b]
map UniqueDef -> (ConstraintNameDB, [FieldNameDB])
udToPair [UniqueDef]
udefs
            -- Check for table existence if there are no columns, workaround
            -- for https://github.com/yesodweb/persistent/issues/152

    createText :: [Column]
-> [ForeignDef] -> [(ConstraintNameDB, [FieldNameDB])] -> [AlterDB]
createText [Column]
newcols [ForeignDef]
fdefs_ [(ConstraintNameDB, [FieldNameDB])]
udspair =
        ([Column] -> EntityDef -> AlterDB
addTable [Column]
newcols EntityDef
entity) AlterDB -> [AlterDB] -> [AlterDB]
forall a. a -> [a] -> [a]
: [AlterDB]
uniques [AlterDB] -> [AlterDB] -> [AlterDB]
forall a. [a] -> [a] -> [a]
++ [AlterDB]
references [AlterDB] -> [AlterDB] -> [AlterDB]
forall a. [a] -> [a] -> [a]
++ [AlterDB]
foreignsAlt
      where
        uniques :: [AlterDB]
uniques = (((ConstraintNameDB, [FieldNameDB]) -> [AlterDB])
 -> [(ConstraintNameDB, [FieldNameDB])] -> [AlterDB])
-> [(ConstraintNameDB, [FieldNameDB])]
-> ((ConstraintNameDB, [FieldNameDB]) -> [AlterDB])
-> [AlterDB]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((ConstraintNameDB, [FieldNameDB]) -> [AlterDB])
-> [(ConstraintNameDB, [FieldNameDB])] -> [AlterDB]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap [(ConstraintNameDB, [FieldNameDB])]
udspair (((ConstraintNameDB, [FieldNameDB]) -> [AlterDB]) -> [AlterDB])
-> ((ConstraintNameDB, [FieldNameDB]) -> [AlterDB]) -> [AlterDB]
forall a b. (a -> b) -> a -> b
$ \(ConstraintNameDB
uname, [FieldNameDB]
ucols) ->
                [EntityNameDB -> AlterTable -> AlterDB
AlterTable EntityNameDB
name (AlterTable -> AlterDB) -> AlterTable -> AlterDB
forall a b. (a -> b) -> a -> b
$ ConstraintNameDB -> [FieldNameDB] -> AlterTable
AddUniqueConstraint ConstraintNameDB
uname [FieldNameDB]
ucols]
        references :: [AlterDB]
references =
            (Column -> Maybe AlterDB) -> [Column] -> [AlterDB]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe
                (\Column { FieldNameDB
cName :: FieldNameDB
cName :: Column -> FieldNameDB
cName, Maybe ColumnReference
cReference :: Column -> Maybe ColumnReference
cReference :: Maybe ColumnReference
cReference } ->
                    [EntityDef]
-> EntityDef -> FieldNameDB -> ColumnReference -> Maybe AlterDB
getAddReference [EntityDef]
allDefs EntityDef
entity FieldNameDB
cName (ColumnReference -> Maybe AlterDB)
-> Maybe ColumnReference -> Maybe AlterDB
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe ColumnReference
cReference
                )
                [Column]
newcols
        foreignsAlt :: [AlterDB]
foreignsAlt = (ForeignDef -> Maybe AlterDB) -> [ForeignDef] -> [AlterDB]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (EntityDef -> ForeignDef -> Maybe AlterDB
mkForeignAlt EntityDef
entity) [ForeignDef]
fdefs_

mkForeignAlt
    :: EntityDef
    -> ForeignDef
    -> Maybe AlterDB
mkForeignAlt :: EntityDef -> ForeignDef -> Maybe AlterDB
mkForeignAlt EntityDef
entity ForeignDef
fdef = AlterDB -> Maybe AlterDB
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AlterDB -> Maybe AlterDB) -> AlterDB -> Maybe AlterDB
forall a b. (a -> b) -> a -> b
$ EntityNameDB -> AlterColumn -> AlterDB
AlterColumn EntityNameDB
tableName_ AlterColumn
addReference
  where
    tableName_ :: EntityNameDB
tableName_ = EntityDef -> EntityNameDB
getEntityDBName EntityDef
entity
    addReference :: AlterColumn
addReference =
        EntityNameDB
-> ConstraintNameDB
-> [FieldNameDB]
-> [Text]
-> FieldCascade
-> AlterColumn
AddReference
            (ForeignDef -> EntityNameDB
foreignRefTableDBName ForeignDef
fdef)
            ConstraintNameDB
constraintName
            [FieldNameDB]
childfields
            [Text]
escapedParentFields
            (ForeignDef -> FieldCascade
foreignFieldCascade ForeignDef
fdef)
    constraintName :: ConstraintNameDB
constraintName =
        ForeignDef -> ConstraintNameDB
foreignConstraintNameDBName ForeignDef
fdef
    ([FieldNameDB]
childfields, [FieldNameDB]
parentfields) =
        [(FieldNameDB, FieldNameDB)] -> ([FieldNameDB], [FieldNameDB])
forall a b. [(a, b)] -> ([a], [b])
unzip ((((FieldNameHS, FieldNameDB), (FieldNameHS, FieldNameDB))
 -> (FieldNameDB, FieldNameDB))
-> [((FieldNameHS, FieldNameDB), (FieldNameHS, FieldNameDB))]
-> [(FieldNameDB, FieldNameDB)]
forall a b. (a -> b) -> [a] -> [b]
map (\((FieldNameHS
_,FieldNameDB
b),(FieldNameHS
_,FieldNameDB
d)) -> (FieldNameDB
b,FieldNameDB
d)) (ForeignDef
-> [((FieldNameHS, FieldNameDB), (FieldNameHS, FieldNameDB))]
foreignFields ForeignDef
fdef))
    escapedParentFields :: [Text]
escapedParentFields =
        (FieldNameDB -> Text) -> [FieldNameDB] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map FieldNameDB -> Text
escapeF [FieldNameDB]
parentfields

addTable :: [Column] -> EntityDef -> AlterDB
addTable :: [Column] -> EntityDef -> AlterDB
addTable [Column]
cols EntityDef
entity =
    Text -> AlterDB
AddTable (Text -> AlterDB) -> Text -> AlterDB
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat
        -- Lower case e: see Database.Persist.Sql.Migration
        [ Text
"CREATe TABLE " -- DO NOT FIX THE CAPITALIZATION!
        , EntityNameDB -> Text
escapeE EntityNameDB
name
        , Text
"("
        , Text
idtxt
        , if [Column] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Column]
nonIdCols then Text
"" else Text
","
        , Text -> [Text] -> Text
T.intercalate Text
"," ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Column -> Text) -> [Column] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Column -> Text
showColumn [Column]
nonIdCols
        , Text
")"
        ]
  where
    nonIdCols :: [Column]
nonIdCols =
        case EntityDef -> Maybe CompositeDef
entityPrimary EntityDef
entity of
            Just CompositeDef
_ ->
                [Column]
cols
            Maybe CompositeDef
_ ->
                (Column -> Bool) -> [Column] -> [Column]
forall a. (a -> Bool) -> [a] -> [a]
filter Column -> Bool
keepField [Column]
cols
      where
        keepField :: Column -> Bool
keepField Column
c =
            FieldNameDB -> Maybe FieldNameDB
forall a. a -> Maybe a
Just (Column -> FieldNameDB
cName Column
c) Maybe FieldNameDB -> Maybe FieldNameDB -> Bool
forall a. Eq a => a -> a -> Bool
/= (FieldDef -> FieldNameDB) -> Maybe FieldDef -> Maybe FieldNameDB
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FieldDef -> FieldNameDB
fieldDB (EntityDef -> Maybe FieldDef
getEntityIdField EntityDef
entity)
            Bool -> Bool -> Bool
&& Bool -> Bool
not (EntityDef -> FieldNameDB -> Bool
safeToRemove EntityDef
entity (Column -> FieldNameDB
cName Column
c))

    name :: EntityNameDB
name =
        EntityDef -> EntityNameDB
getEntityDBName EntityDef
entity
    idtxt :: Text
idtxt =
        case EntityDef -> EntityIdDef
getEntityId EntityDef
entity of
            EntityIdNaturalKey CompositeDef
pdef ->
                [Text] -> Text
T.concat
                    [ Text
" PRIMARY KEY ("
                    , Text -> [Text] -> Text
T.intercalate Text
"," ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (FieldDef -> Text) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (FieldNameDB -> Text
escapeF (FieldNameDB -> Text)
-> (FieldDef -> FieldNameDB) -> FieldDef -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldDef -> FieldNameDB
fieldDB) ([FieldDef] -> [Text]) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> a -> b
$ NonEmpty FieldDef -> [FieldDef]
forall a. NonEmpty a -> [a]
NEL.toList (NonEmpty FieldDef -> [FieldDef])
-> NonEmpty FieldDef -> [FieldDef]
forall a b. (a -> b) -> a -> b
$ CompositeDef -> NonEmpty FieldDef
compositeFields CompositeDef
pdef
                    , Text
")"
                    ]
            EntityIdField FieldDef
field ->
                let defText :: Maybe Text
defText = [FieldAttr] -> Maybe Text
defaultAttribute ([FieldAttr] -> Maybe Text) -> [FieldAttr] -> Maybe Text
forall a b. (a -> b) -> a -> b
$ FieldDef -> [FieldAttr]
fieldAttrs FieldDef
field
                    sType :: SqlType
sType = FieldDef -> SqlType
fieldSqlType FieldDef
field
                in  [Text] -> Text
T.concat
                        [ FieldNameDB -> Text
escapeF (FieldNameDB -> Text) -> FieldNameDB -> Text
forall a b. (a -> b) -> a -> b
$ FieldDef -> FieldNameDB
fieldDB FieldDef
field
                        , SqlType -> Maybe Text -> Text
maySerial SqlType
sType Maybe Text
defText
                        , Text
" PRIMARY KEY UNIQUE"
                        , Maybe Text -> Text
mayDefault Maybe Text
defText
                        ]

maySerial :: SqlType -> Maybe Text -> Text
maySerial :: SqlType -> Maybe Text -> Text
maySerial SqlType
SqlInt64 Maybe Text
Nothing = Text
" SERIAL8 "
maySerial SqlType
sType Maybe Text
_ = Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SqlType -> Text
showSqlType SqlType
sType

mayDefault :: Maybe Text -> Text
mayDefault :: Maybe Text -> Text
mayDefault Maybe Text
def = case Maybe Text
def of
    Maybe Text
Nothing -> Text
""
    Just Text
d -> Text
" DEFAULT " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
d

type SafeToRemove = Bool

data AlterColumn
    = ChangeType Column SqlType Text
    | IsNull Column
    | NotNull Column
    | Add' Column
    | Drop Column SafeToRemove
    | Default Column Text
    | NoDefault Column
    | Update' Column Text
    | AddReference EntityNameDB ConstraintNameDB [FieldNameDB] [Text] FieldCascade
    | DropReference ConstraintNameDB
    deriving Int -> AlterColumn -> ShowS
[AlterColumn] -> ShowS
AlterColumn -> String
(Int -> AlterColumn -> ShowS)
-> (AlterColumn -> String)
-> ([AlterColumn] -> ShowS)
-> Show AlterColumn
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AlterColumn] -> ShowS
$cshowList :: [AlterColumn] -> ShowS
show :: AlterColumn -> String
$cshow :: AlterColumn -> String
showsPrec :: Int -> AlterColumn -> ShowS
$cshowsPrec :: Int -> AlterColumn -> ShowS
Show

data AlterTable
    = AddUniqueConstraint ConstraintNameDB [FieldNameDB]
    | DropConstraint ConstraintNameDB
    deriving Int -> AlterTable -> ShowS
[AlterTable] -> ShowS
AlterTable -> String
(Int -> AlterTable -> ShowS)
-> (AlterTable -> String)
-> ([AlterTable] -> ShowS)
-> Show AlterTable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AlterTable] -> ShowS
$cshowList :: [AlterTable] -> ShowS
show :: AlterTable -> String
$cshow :: AlterTable -> String
showsPrec :: Int -> AlterTable -> ShowS
$cshowsPrec :: Int -> AlterTable -> ShowS
Show

data AlterDB = AddTable Text
             | AlterColumn EntityNameDB AlterColumn
             | AlterTable EntityNameDB AlterTable
             deriving Int -> AlterDB -> ShowS
[AlterDB] -> ShowS
AlterDB -> String
(Int -> AlterDB -> ShowS)
-> (AlterDB -> String) -> ([AlterDB] -> ShowS) -> Show AlterDB
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AlterDB] -> ShowS
$cshowList :: [AlterDB] -> ShowS
show :: AlterDB -> String
$cshow :: AlterDB -> String
showsPrec :: Int -> AlterDB -> ShowS
$cshowsPrec :: Int -> AlterDB -> ShowS
Show

-- | Returns all of the columns in the given table currently in the database.
getColumns :: (Text -> IO Statement)
           -> EntityDef -> [Column]
           -> IO [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
getColumns :: (Text -> IO Statement)
-> EntityDef
-> [Column]
-> IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
getColumns Text -> IO Statement
getter EntityDef
def [Column]
cols = do
    let sqlv :: Text
sqlv = [Text] -> Text
T.concat
            [ Text
"SELECT "
            , Text
"column_name "
            , Text
",is_nullable "
            , Text
",COALESCE(domain_name, udt_name)" -- See DOMAINS below
            , Text
",column_default "
            , Text
",generation_expression "
            , Text
",numeric_precision "
            , Text
",numeric_scale "
            , Text
",character_maximum_length "
            , Text
"FROM information_schema.columns "
            , Text
"WHERE table_catalog=current_database() "
            , Text
"AND table_schema=current_schema() "
            , Text
"AND table_name=? "
            ]

-- DOMAINS Postgres supports the concept of domains, which are data types
-- with optional constraints.  An app might make an "email" domain over the
-- varchar type, with a CHECK that the emails are valid In this case the
-- generated SQL should use the domain name: ALTER TABLE users ALTER COLUMN
-- foo TYPE email This code exists to use the domain name (email), instead
-- of the underlying type (varchar).  This is tested in
-- EquivalentTypeTest.hs

    Statement
stmt <- Text -> IO Statement
getter Text
sqlv
    let vals :: [PersistValue]
vals =
            [ Text -> PersistValue
PersistText (Text -> PersistValue) -> Text -> PersistValue
forall a b. (a -> b) -> a -> b
$ EntityNameDB -> Text
unEntityNameDB (EntityNameDB -> Text) -> EntityNameDB -> Text
forall a b. (a -> b) -> a -> b
$ EntityDef -> EntityNameDB
getEntityDBName EntityDef
def
            ]
    [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
columns <- Acquire (ConduitM () [PersistValue] IO ())
-> (ConduitM () [PersistValue] IO ()
    -> IO
         [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))])
-> IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall (m :: * -> *) a b.
MonadUnliftIO m =>
Acquire a -> (a -> m b) -> m b
with (Statement
-> [PersistValue] -> Acquire (ConduitM () [PersistValue] IO ())
Statement
-> forall (m :: * -> *).
   MonadIO m =>
   [PersistValue] -> Acquire (ConduitM () [PersistValue] m ())
stmtQuery Statement
stmt [PersistValue]
vals) (\ConduitM () [PersistValue] IO ()
src -> ConduitT
  ()
  Void
  IO
  [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
-> IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit (ConduitT
   ()
   Void
   IO
   [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
 -> IO
      [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))])
-> ConduitT
     ()
     Void
     IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
-> IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall a b. (a -> b) -> a -> b
$ ConduitM () [PersistValue] IO ()
src ConduitM () [PersistValue] IO ()
-> ConduitM
     [PersistValue]
     Void
     IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
-> ConduitT
     ()
     Void
     IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.| ConduitT
  [PersistValue]
  (Either Text (Either Column (ConstraintNameDB, [FieldNameDB])))
  IO
  ()
processColumns ConduitT
  [PersistValue]
  (Either Text (Either Column (ConstraintNameDB, [FieldNameDB])))
  IO
  ()
-> ConduitM
     (Either Text (Either Column (ConstraintNameDB, [FieldNameDB])))
     Void
     IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
-> ConduitM
     [PersistValue]
     Void
     IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.| ConduitM
  (Either Text (Either Column (ConstraintNameDB, [FieldNameDB])))
  Void
  IO
  [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall (m :: * -> *) a o. Monad m => ConduitT a o m [a]
CL.consume)
    let sqlc :: Text
sqlc = [Text] -> Text
T.concat
            [ Text
"SELECT "
            , Text
"c.constraint_name, "
            , Text
"c.column_name "
            , Text
"FROM information_schema.key_column_usage AS c, "
            , Text
"information_schema.table_constraints AS k "
            , Text
"WHERE c.table_catalog=current_database() "
            , Text
"AND c.table_catalog=k.table_catalog "
            , Text
"AND c.table_schema=current_schema() "
            , Text
"AND c.table_schema=k.table_schema "
            , Text
"AND c.table_name=? "
            , Text
"AND c.table_name=k.table_name "
            , Text
"AND c.constraint_name=k.constraint_name "
            , Text
"AND NOT k.constraint_type IN ('PRIMARY KEY', 'FOREIGN KEY') "
            , Text
"ORDER BY c.constraint_name, c.column_name"
            ]

    Statement
stmt' <- Text -> IO Statement
getter Text
sqlc

    [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
us <- Acquire (ConduitM () [PersistValue] IO ())
-> (ConduitM () [PersistValue] IO ()
    -> IO
         [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))])
-> IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall (m :: * -> *) a b.
MonadUnliftIO m =>
Acquire a -> (a -> m b) -> m b
with (Statement
-> [PersistValue] -> Acquire (ConduitM () [PersistValue] IO ())
Statement
-> forall (m :: * -> *).
   MonadIO m =>
   [PersistValue] -> Acquire (ConduitM () [PersistValue] m ())
stmtQuery Statement
stmt' [PersistValue]
vals) (\ConduitM () [PersistValue] IO ()
src -> ConduitT
  ()
  Void
  IO
  [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
-> IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit (ConduitT
   ()
   Void
   IO
   [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
 -> IO
      [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))])
-> ConduitT
     ()
     Void
     IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
-> IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall a b. (a -> b) -> a -> b
$ ConduitM () [PersistValue] IO ()
src ConduitM () [PersistValue] IO ()
-> ConduitM
     [PersistValue]
     Void
     IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
-> ConduitT
     ()
     Void
     IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.| ConduitM
  [PersistValue]
  Void
  IO
  [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
helperU)
    [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
-> IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
 -> IO
      [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))])
-> [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
-> IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall a b. (a -> b) -> a -> b
$ [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
columns [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
-> [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
-> [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall a. [a] -> [a] -> [a]
++ [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
us
  where
    refMap :: Map Text (EntityNameDB, ConstraintNameDB)
refMap =
        (ColumnReference -> (EntityNameDB, ConstraintNameDB))
-> Map Text ColumnReference
-> Map Text (EntityNameDB, ConstraintNameDB)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ColumnReference
cr -> (ColumnReference -> EntityNameDB
crTableName ColumnReference
cr, ColumnReference -> ConstraintNameDB
crConstraintName ColumnReference
cr))
        (Map Text ColumnReference
 -> Map Text (EntityNameDB, ConstraintNameDB))
-> Map Text ColumnReference
-> Map Text (EntityNameDB, ConstraintNameDB)
forall a b. (a -> b) -> a -> b
$ [(Text, ColumnReference)] -> Map Text ColumnReference
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
        ([(Text, ColumnReference)] -> Map Text ColumnReference)
-> [(Text, ColumnReference)] -> Map Text ColumnReference
forall a b. (a -> b) -> a -> b
$ ([(Text, ColumnReference)] -> Column -> [(Text, ColumnReference)])
-> [(Text, ColumnReference)]
-> [Column]
-> [(Text, ColumnReference)]
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' [(Text, ColumnReference)] -> Column -> [(Text, ColumnReference)]
ref [] [Column]
cols
      where
        ref :: [(Text, ColumnReference)] -> Column -> [(Text, ColumnReference)]
ref [(Text, ColumnReference)]
rs Column
c =
            [(Text, ColumnReference)]
-> (ColumnReference -> [(Text, ColumnReference)])
-> Maybe ColumnReference
-> [(Text, ColumnReference)]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [(Text, ColumnReference)]
rs (\ColumnReference
r -> (FieldNameDB -> Text
unFieldNameDB (FieldNameDB -> Text) -> FieldNameDB -> Text
forall a b. (a -> b) -> a -> b
$ Column -> FieldNameDB
cName Column
c, ColumnReference
r) (Text, ColumnReference)
-> [(Text, ColumnReference)] -> [(Text, ColumnReference)]
forall a. a -> [a] -> [a]
: [(Text, ColumnReference)]
rs) (Column -> Maybe ColumnReference
cReference Column
c)
    getAll :: ConduitT [PersistValue] (Text, Text) IO ()
getAll =
        ([PersistValue] -> IO (Text, Text))
-> ConduitT [PersistValue] (Text, Text) IO ()
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ConduitT a b m ()
CL.mapM (([PersistValue] -> IO (Text, Text))
 -> ConduitT [PersistValue] (Text, Text) IO ())
-> ([PersistValue] -> IO (Text, Text))
-> ConduitT [PersistValue] (Text, Text) IO ()
forall a b. (a -> b) -> a -> b
$ \[PersistValue]
x ->
            (Text, Text) -> IO (Text, Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Text, Text) -> IO (Text, Text))
-> (Text, Text) -> IO (Text, Text)
forall a b. (a -> b) -> a -> b
$ case [PersistValue]
x of
                [PersistText Text
con, PersistText Text
col] ->
                    (Text
con, Text
col)
                [PersistByteString ConnectionString
con, PersistByteString ConnectionString
col] ->
                    (ConnectionString -> Text
T.decodeUtf8 ConnectionString
con, ConnectionString -> Text
T.decodeUtf8 ConnectionString
col)
                [PersistValue]
o ->
                    String -> (Text, Text)
forall a. HasCallStack => String -> a
error (String -> (Text, Text)) -> String -> (Text, Text)
forall a b. (a -> b) -> a -> b
$ String
"unexpected datatype returned for postgres o="String -> ShowS
forall a. [a] -> [a] -> [a]
++[PersistValue] -> String
forall a. Show a => a -> String
show [PersistValue]
o
    helperU :: ConduitM
  [PersistValue]
  Void
  IO
  [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
helperU = do
        [(Text, Text)]
rows <- ConduitT [PersistValue] (Text, Text) IO ()
getAll ConduitT [PersistValue] (Text, Text) IO ()
-> ConduitM (Text, Text) Void IO [(Text, Text)]
-> ConduitM [PersistValue] Void IO [(Text, Text)]
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.| ConduitM (Text, Text) Void IO [(Text, Text)]
forall (m :: * -> *) a o. Monad m => ConduitT a o m [a]
CL.consume
        [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
-> ConduitM
     [PersistValue]
     Void
     IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
 -> ConduitM
      [PersistValue]
      Void
      IO
      [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))])
-> [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
-> ConduitM
     [PersistValue]
     Void
     IO
     [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall a b. (a -> b) -> a -> b
$ ([(Text, Text)]
 -> Either Text (Either Column (ConstraintNameDB, [FieldNameDB])))
-> [[(Text, Text)]]
-> [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall a b. (a -> b) -> [a] -> [b]
map (Either Column (ConstraintNameDB, [FieldNameDB])
-> Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))
forall a b. b -> Either a b
Right (Either Column (ConstraintNameDB, [FieldNameDB])
 -> Either Text (Either Column (ConstraintNameDB, [FieldNameDB])))
-> ([(Text, Text)]
    -> Either Column (ConstraintNameDB, [FieldNameDB]))
-> [(Text, Text)]
-> Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ConstraintNameDB, [FieldNameDB])
-> Either Column (ConstraintNameDB, [FieldNameDB])
forall a b. b -> Either a b
Right ((ConstraintNameDB, [FieldNameDB])
 -> Either Column (ConstraintNameDB, [FieldNameDB]))
-> ([(Text, Text)] -> (ConstraintNameDB, [FieldNameDB]))
-> [(Text, Text)]
-> Either Column (ConstraintNameDB, [FieldNameDB])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> ConstraintNameDB
ConstraintNameDB (Text -> ConstraintNameDB)
-> ([(Text, Text)] -> Text) -> [(Text, Text)] -> ConstraintNameDB
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> Text
forall a b. (a, b) -> a
fst ((Text, Text) -> Text)
-> ([(Text, Text)] -> (Text, Text)) -> [(Text, Text)] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Text, Text)] -> (Text, Text)
forall a. [a] -> a
head ([(Text, Text)] -> ConstraintNameDB)
-> ([(Text, Text)] -> [FieldNameDB])
-> [(Text, Text)]
-> (ConstraintNameDB, [FieldNameDB])
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& ((Text, Text) -> FieldNameDB) -> [(Text, Text)] -> [FieldNameDB]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> FieldNameDB
FieldNameDB (Text -> FieldNameDB)
-> ((Text, Text) -> Text) -> (Text, Text) -> FieldNameDB
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> Text
forall a b. (a, b) -> b
snd)))
               ([[(Text, Text)]]
 -> [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))])
-> [[(Text, Text)]]
-> [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
forall a b. (a -> b) -> a -> b
$ ((Text, Text) -> (Text, Text) -> Bool)
-> [(Text, Text)] -> [[(Text, Text)]]
forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
(==) (Text -> Text -> Bool)
-> ((Text, Text) -> Text) -> (Text, Text) -> (Text, Text) -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (Text, Text) -> Text
forall a b. (a, b) -> a
fst) [(Text, Text)]
rows
    processColumns :: ConduitT
  [PersistValue]
  (Either Text (Either Column (ConstraintNameDB, [FieldNameDB])))
  IO
  ()
processColumns =
        ([PersistValue]
 -> IO
      (Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))))
-> ConduitT
     [PersistValue]
     (Either Text (Either Column (ConstraintNameDB, [FieldNameDB])))
     IO
     ()
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ConduitT a b m ()
CL.mapM (([PersistValue]
  -> IO
       (Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))))
 -> ConduitT
      [PersistValue]
      (Either Text (Either Column (ConstraintNameDB, [FieldNameDB])))
      IO
      ())
-> ([PersistValue]
    -> IO
         (Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))))
-> ConduitT
     [PersistValue]
     (Either Text (Either Column (ConstraintNameDB, [FieldNameDB])))
     IO
     ()
forall a b. (a -> b) -> a -> b
$ \x' :: [PersistValue]
x'@((PersistText Text
cname) : [PersistValue]
_) -> do
            Either Text Column
col <- IO (Either Text Column) -> IO (Either Text Column)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either Text Column) -> IO (Either Text Column))
-> IO (Either Text Column) -> IO (Either Text Column)
forall a b. (a -> b) -> a -> b
$ (Text -> IO Statement)
-> EntityNameDB
-> [PersistValue]
-> Maybe (EntityNameDB, ConstraintNameDB)
-> IO (Either Text Column)
getColumn Text -> IO Statement
getter (EntityDef -> EntityNameDB
getEntityDBName EntityDef
def) [PersistValue]
x' (Text
-> Map Text (EntityNameDB, ConstraintNameDB)
-> Maybe (EntityNameDB, ConstraintNameDB)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
cname Map Text (EntityNameDB, ConstraintNameDB)
refMap)
            Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))
-> IO
     (Either Text (Either Column (ConstraintNameDB, [FieldNameDB])))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))
 -> IO
      (Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))))
-> Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))
-> IO
     (Either Text (Either Column (ConstraintNameDB, [FieldNameDB])))
forall a b. (a -> b) -> a -> b
$ case Either Text Column
col of
                Left Text
e -> Text
-> Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))
forall a b. a -> Either a b
Left Text
e
                Right Column
c -> Either Column (ConstraintNameDB, [FieldNameDB])
-> Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))
forall a b. b -> Either a b
Right (Either Column (ConstraintNameDB, [FieldNameDB])
 -> Either Text (Either Column (ConstraintNameDB, [FieldNameDB])))
-> Either Column (ConstraintNameDB, [FieldNameDB])
-> Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))
forall a b. (a -> b) -> a -> b
$ Column -> Either Column (ConstraintNameDB, [FieldNameDB])
forall a b. a -> Either a b
Left Column
c

-- | Check if a column name is listed as the "safe to remove" in the entity
-- list.
safeToRemove :: EntityDef -> FieldNameDB -> Bool
safeToRemove :: EntityDef -> FieldNameDB -> Bool
safeToRemove EntityDef
def (FieldNameDB Text
colName)
    = (FieldDef -> Bool) -> [FieldDef] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (FieldAttr -> [FieldAttr] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem FieldAttr
FieldAttrSafeToRemove ([FieldAttr] -> Bool)
-> (FieldDef -> [FieldAttr]) -> FieldDef -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldDef -> [FieldAttr]
fieldAttrs)
    ([FieldDef] -> Bool) -> [FieldDef] -> Bool
forall a b. (a -> b) -> a -> b
$ (FieldDef -> Bool) -> [FieldDef] -> [FieldDef]
forall a. (a -> Bool) -> [a] -> [a]
filter ((FieldNameDB -> FieldNameDB -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> FieldNameDB
FieldNameDB Text
colName) (FieldNameDB -> Bool)
-> (FieldDef -> FieldNameDB) -> FieldDef -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldDef -> FieldNameDB
fieldDB)
    ([FieldDef] -> [FieldDef]) -> [FieldDef] -> [FieldDef]
forall a b. (a -> b) -> a -> b
$ [FieldDef]
allEntityFields
  where
    allEntityFields :: [FieldDef]
allEntityFields =
        EntityDef -> [FieldDef]
getEntityFieldsDatabase EntityDef
def [FieldDef] -> [FieldDef] -> [FieldDef]
forall a. Semigroup a => a -> a -> a
<> case EntityDef -> EntityIdDef
getEntityId EntityDef
def of
            EntityIdField FieldDef
fdef ->
                [FieldDef
fdef]
            EntityIdDef
_ ->
                []

getAlters :: [EntityDef]
          -> EntityDef
          -> ([Column], [(ConstraintNameDB, [FieldNameDB])])
          -> ([Column], [(ConstraintNameDB, [FieldNameDB])])
          -> ([AlterColumn], [AlterTable])
getAlters :: [EntityDef]
-> EntityDef
-> ([Column], [(ConstraintNameDB, [FieldNameDB])])
-> ([Column], [(ConstraintNameDB, [FieldNameDB])])
-> ([AlterColumn], [AlterTable])
getAlters [EntityDef]
defs EntityDef
def ([Column]
c1, [(ConstraintNameDB, [FieldNameDB])]
u1) ([Column]
c2, [(ConstraintNameDB, [FieldNameDB])]
u2) =
    ([Column] -> [Column] -> [AlterColumn]
getAltersC [Column]
c1 [Column]
c2, [(ConstraintNameDB, [FieldNameDB])]
-> [(ConstraintNameDB, [FieldNameDB])] -> [AlterTable]
getAltersU [(ConstraintNameDB, [FieldNameDB])]
u1 [(ConstraintNameDB, [FieldNameDB])]
u2)
  where
    getAltersC :: [Column] -> [Column] -> [AlterColumn]
getAltersC [] [Column]
old =
        (Column -> AlterColumn) -> [Column] -> [AlterColumn]
forall a b. (a -> b) -> [a] -> [b]
map (\Column
x -> Column -> Bool -> AlterColumn
Drop Column
x (Bool -> AlterColumn) -> Bool -> AlterColumn
forall a b. (a -> b) -> a -> b
$ EntityDef -> FieldNameDB -> Bool
safeToRemove EntityDef
def (FieldNameDB -> Bool) -> FieldNameDB -> Bool
forall a b. (a -> b) -> a -> b
$ Column -> FieldNameDB
cName Column
x) [Column]
old
    getAltersC (Column
new:[Column]
news) [Column]
old =
        let ([AlterColumn]
alters, [Column]
old') = [EntityDef]
-> EntityDef -> Column -> [Column] -> ([AlterColumn], [Column])
findAlters [EntityDef]
defs EntityDef
def Column
new [Column]
old
         in [AlterColumn]
alters [AlterColumn] -> [AlterColumn] -> [AlterColumn]
forall a. [a] -> [a] -> [a]
++ [Column] -> [Column] -> [AlterColumn]
getAltersC [Column]
news [Column]
old'

    getAltersU
        :: [(ConstraintNameDB, [FieldNameDB])]
        -> [(ConstraintNameDB, [FieldNameDB])]
        -> [AlterTable]
    getAltersU :: [(ConstraintNameDB, [FieldNameDB])]
-> [(ConstraintNameDB, [FieldNameDB])] -> [AlterTable]
getAltersU [] [(ConstraintNameDB, [FieldNameDB])]
old =
        (ConstraintNameDB -> AlterTable)
-> [ConstraintNameDB] -> [AlterTable]
forall a b. (a -> b) -> [a] -> [b]
map ConstraintNameDB -> AlterTable
DropConstraint ([ConstraintNameDB] -> [AlterTable])
-> [ConstraintNameDB] -> [AlterTable]
forall a b. (a -> b) -> a -> b
$ (ConstraintNameDB -> Bool)
-> [ConstraintNameDB] -> [ConstraintNameDB]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> (ConstraintNameDB -> Bool) -> ConstraintNameDB -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstraintNameDB -> Bool
isManual) ([ConstraintNameDB] -> [ConstraintNameDB])
-> [ConstraintNameDB] -> [ConstraintNameDB]
forall a b. (a -> b) -> a -> b
$ ((ConstraintNameDB, [FieldNameDB]) -> ConstraintNameDB)
-> [(ConstraintNameDB, [FieldNameDB])] -> [ConstraintNameDB]
forall a b. (a -> b) -> [a] -> [b]
map (ConstraintNameDB, [FieldNameDB]) -> ConstraintNameDB
forall a b. (a, b) -> a
fst [(ConstraintNameDB, [FieldNameDB])]
old
    getAltersU ((ConstraintNameDB
name, [FieldNameDB]
cols):[(ConstraintNameDB, [FieldNameDB])]
news) [(ConstraintNameDB, [FieldNameDB])]
old =
        case ConstraintNameDB
-> [(ConstraintNameDB, [FieldNameDB])] -> Maybe [FieldNameDB]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup ConstraintNameDB
name [(ConstraintNameDB, [FieldNameDB])]
old of
            Maybe [FieldNameDB]
Nothing ->
                ConstraintNameDB -> [FieldNameDB] -> AlterTable
AddUniqueConstraint ConstraintNameDB
name [FieldNameDB]
cols AlterTable -> [AlterTable] -> [AlterTable]
forall a. a -> [a] -> [a]
: [(ConstraintNameDB, [FieldNameDB])]
-> [(ConstraintNameDB, [FieldNameDB])] -> [AlterTable]
getAltersU [(ConstraintNameDB, [FieldNameDB])]
news [(ConstraintNameDB, [FieldNameDB])]
old
            Just [FieldNameDB]
ocols ->
                let old' :: [(ConstraintNameDB, [FieldNameDB])]
old' = ((ConstraintNameDB, [FieldNameDB]) -> Bool)
-> [(ConstraintNameDB, [FieldNameDB])]
-> [(ConstraintNameDB, [FieldNameDB])]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(ConstraintNameDB
x, [FieldNameDB]
_) -> ConstraintNameDB
x ConstraintNameDB -> ConstraintNameDB -> Bool
forall a. Eq a => a -> a -> Bool
/= ConstraintNameDB
name) [(ConstraintNameDB, [FieldNameDB])]
old
                 in if [FieldNameDB] -> [FieldNameDB]
forall a. Ord a => [a] -> [a]
sort [FieldNameDB]
cols [FieldNameDB] -> [FieldNameDB] -> Bool
forall a. Eq a => a -> a -> Bool
== [FieldNameDB] -> [FieldNameDB]
forall a. Ord a => [a] -> [a]
sort [FieldNameDB]
ocols
                        then [(ConstraintNameDB, [FieldNameDB])]
-> [(ConstraintNameDB, [FieldNameDB])] -> [AlterTable]
getAltersU [(ConstraintNameDB, [FieldNameDB])]
news [(ConstraintNameDB, [FieldNameDB])]
old'
                        else  ConstraintNameDB -> AlterTable
DropConstraint ConstraintNameDB
name
                            AlterTable -> [AlterTable] -> [AlterTable]
forall a. a -> [a] -> [a]
: ConstraintNameDB -> [FieldNameDB] -> AlterTable
AddUniqueConstraint ConstraintNameDB
name [FieldNameDB]
cols
                            AlterTable -> [AlterTable] -> [AlterTable]
forall a. a -> [a] -> [a]
: [(ConstraintNameDB, [FieldNameDB])]
-> [(ConstraintNameDB, [FieldNameDB])] -> [AlterTable]
getAltersU [(ConstraintNameDB, [FieldNameDB])]
news [(ConstraintNameDB, [FieldNameDB])]
old'

    -- Don't drop constraints which were manually added.
    isManual :: ConstraintNameDB -> Bool
isManual (ConstraintNameDB Text
x) = Text
"__manual_" Text -> Text -> Bool
`T.isPrefixOf` Text
x

getColumn
    :: (Text -> IO Statement)
    -> EntityNameDB
    -> [PersistValue]
    -> Maybe (EntityNameDB, ConstraintNameDB)
    -> IO (Either Text Column)
getColumn :: (Text -> IO Statement)
-> EntityNameDB
-> [PersistValue]
-> Maybe (EntityNameDB, ConstraintNameDB)
-> IO (Either Text Column)
getColumn Text -> IO Statement
getter EntityNameDB
tableName' [ PersistText Text
columnName
                            , PersistText Text
isNullable
                            , PersistText Text
typeName
                            , PersistValue
defaultValue
                            , PersistValue
generationExpression
                            , PersistValue
numericPrecision
                            , PersistValue
numericScale
                            , PersistValue
maxlen
                            ] Maybe (EntityNameDB, ConstraintNameDB)
refName_ = ExceptT Text IO Column -> IO (Either Text Column)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT Text IO Column -> IO (Either Text Column))
-> ExceptT Text IO Column -> IO (Either Text Column)
forall a b. (a -> b) -> a -> b
$ do
    Maybe Text
defaultValue' <-
        case PersistValue
defaultValue of
            PersistValue
PersistNull ->
                Maybe Text -> ExceptT Text IO (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Text
forall a. Maybe a
Nothing
            PersistText Text
t ->
                Maybe Text -> ExceptT Text IO (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe Text -> ExceptT Text IO (Maybe Text))
-> Maybe Text -> ExceptT Text IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t
            PersistValue
_ ->
                Text -> ExceptT Text IO (Maybe Text)
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ExceptT Text IO (Maybe Text))
-> Text -> ExceptT Text IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"Invalid default column: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ PersistValue -> String
forall a. Show a => a -> String
show PersistValue
defaultValue

    Maybe Text
generationExpression' <-
        case PersistValue
generationExpression of
            PersistValue
PersistNull ->
                Maybe Text -> ExceptT Text IO (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Text
forall a. Maybe a
Nothing
            PersistText Text
t ->
                Maybe Text -> ExceptT Text IO (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe Text -> ExceptT Text IO (Maybe Text))
-> Maybe Text -> ExceptT Text IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t
            PersistValue
_ ->
                Text -> ExceptT Text IO (Maybe Text)
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ExceptT Text IO (Maybe Text))
-> Text -> ExceptT Text IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"Invalid generated column: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ PersistValue -> String
forall a. Show a => a -> String
show PersistValue
generationExpression

    let typeStr :: Text
typeStr =
            case PersistValue
maxlen of
                PersistInt64 Int64
n ->
                    [Text] -> Text
T.concat [Text
typeName, Text
"(", String -> Text
T.pack (Int64 -> String
forall a. Show a => a -> String
show Int64
n), Text
")"]
                PersistValue
_ ->
                    Text
typeName

    SqlType
t <- Text -> ExceptT Text IO SqlType
getType Text
typeStr

    let cname :: FieldNameDB
cname = Text -> FieldNameDB
FieldNameDB Text
columnName

    Maybe (EntityNameDB, ConstraintNameDB, Text, Text)
ref <- IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
-> ExceptT
     Text IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
 -> ExceptT
      Text IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text)))
-> IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
-> ExceptT
     Text IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
forall a b. (a -> b) -> a -> b
$ (Maybe (Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
 -> Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
-> IO (Maybe (Maybe (EntityNameDB, ConstraintNameDB, Text, Text)))
-> IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe (Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
-> Maybe (EntityNameDB, ConstraintNameDB, Text, Text)
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (IO (Maybe (Maybe (EntityNameDB, ConstraintNameDB, Text, Text)))
 -> IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text)))
-> IO (Maybe (Maybe (EntityNameDB, ConstraintNameDB, Text, Text)))
-> IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
forall a b. (a -> b) -> a -> b
$ ((EntityNameDB, ConstraintNameDB)
 -> IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text)))
-> Maybe (EntityNameDB, ConstraintNameDB)
-> IO (Maybe (Maybe (EntityNameDB, ConstraintNameDB, Text, Text)))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (FieldNameDB
-> (EntityNameDB, ConstraintNameDB)
-> IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
getRef FieldNameDB
cname) Maybe (EntityNameDB, ConstraintNameDB)
refName_

    Column -> ExceptT Text IO Column
forall (m :: * -> *) a. Monad m => a -> m a
return Column :: FieldNameDB
-> Bool
-> SqlType
-> Maybe Text
-> Maybe Text
-> Maybe ConstraintNameDB
-> Maybe Integer
-> Maybe ColumnReference
-> Column
Column
        { cName :: FieldNameDB
cName = FieldNameDB
cname
        , cNull :: Bool
cNull = Text
isNullable Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"YES"
        , cSqlType :: SqlType
cSqlType = SqlType
t
        , cDefault :: Maybe Text
cDefault = (Text -> Text) -> Maybe Text -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
stripSuffixes Maybe Text
defaultValue'
        , cGenerated :: Maybe Text
cGenerated = (Text -> Text) -> Maybe Text -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
stripSuffixes Maybe Text
generationExpression'
        , cDefaultConstraintName :: Maybe ConstraintNameDB
cDefaultConstraintName = Maybe ConstraintNameDB
forall a. Maybe a
Nothing
        , cMaxLen :: Maybe Integer
cMaxLen = Maybe Integer
forall a. Maybe a
Nothing
        , cReference :: Maybe ColumnReference
cReference = ((EntityNameDB, ConstraintNameDB, Text, Text) -> ColumnReference)
-> Maybe (EntityNameDB, ConstraintNameDB, Text, Text)
-> Maybe ColumnReference
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(EntityNameDB
a,ConstraintNameDB
b,Text
c,Text
d) -> EntityNameDB -> ConstraintNameDB -> FieldCascade -> ColumnReference
ColumnReference EntityNameDB
a ConstraintNameDB
b (Text -> Text -> FieldCascade
forall a a.
(Eq a, Eq a, IsString a, IsString a, Show a, Show a) =>
a -> a -> FieldCascade
mkCascade Text
c Text
d)) Maybe (EntityNameDB, ConstraintNameDB, Text, Text)
ref
        }

  where

    mkCascade :: a -> a -> FieldCascade
mkCascade a
updText a
delText =
        FieldCascade :: Maybe CascadeAction -> Maybe CascadeAction -> FieldCascade
FieldCascade
            { fcOnUpdate :: Maybe CascadeAction
fcOnUpdate = a -> Maybe CascadeAction
forall a. (Eq a, IsString a, Show a) => a -> Maybe CascadeAction
parseCascade a
updText
            , fcOnDelete :: Maybe CascadeAction
fcOnDelete = a -> Maybe CascadeAction
forall a. (Eq a, IsString a, Show a) => a -> Maybe CascadeAction
parseCascade a
delText
            }

    parseCascade :: a -> Maybe CascadeAction
parseCascade a
txt =
        case a
txt of
            a
"NO ACTION" ->
                Maybe CascadeAction
forall a. Maybe a
Nothing
            a
"CASCADE" ->
                CascadeAction -> Maybe CascadeAction
forall a. a -> Maybe a
Just CascadeAction
Cascade
            a
"SET NULL" ->
                CascadeAction -> Maybe CascadeAction
forall a. a -> Maybe a
Just CascadeAction
SetNull
            a
"SET DEFAULT" ->
                CascadeAction -> Maybe CascadeAction
forall a. a -> Maybe a
Just CascadeAction
SetDefault
            a
"RESTRICT" ->
                CascadeAction -> Maybe CascadeAction
forall a. a -> Maybe a
Just CascadeAction
Restrict
            a
_ ->
                String -> Maybe CascadeAction
forall a. HasCallStack => String -> a
error (String -> Maybe CascadeAction) -> String -> Maybe CascadeAction
forall a b. (a -> b) -> a -> b
$ String
"Unexpected value in parseCascade: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> a -> String
forall a. Show a => a -> String
show a
txt

    stripSuffixes :: Text -> Text
stripSuffixes Text
t =
        [Text] -> Text
loop'
            [ Text
"::character varying"
            , Text
"::text"
            ]
      where
        loop' :: [Text] -> Text
loop' [] = Text
t
        loop' (Text
p:[Text]
ps) =
            case Text -> Text -> Maybe Text
T.stripSuffix Text
p Text
t of
                Maybe Text
Nothing -> [Text] -> Text
loop' [Text]
ps
                Just Text
t' -> Text
t'

    getRef :: FieldNameDB
-> (EntityNameDB, ConstraintNameDB)
-> IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
getRef FieldNameDB
cname (EntityNameDB
_, ConstraintNameDB
refName') = do
        let sql :: Text
sql = [Text] -> Text
T.concat
                [ Text
"SELECT DISTINCT "
                , Text
"ccu.table_name, "
                , Text
"tc.constraint_name, "
                , Text
"rc.update_rule, "
                , Text
"rc.delete_rule "
                , Text
"FROM information_schema.constraint_column_usage ccu "
                , Text
"INNER JOIN information_schema.key_column_usage kcu "
                , Text
"  ON ccu.constraint_name = kcu.constraint_name "
                , Text
"INNER JOIN information_schema.table_constraints tc "
                , Text
"  ON tc.constraint_name = kcu.constraint_name "
                , Text
"LEFT JOIN information_schema.referential_constraints AS rc"
                , Text
"  ON rc.constraint_name = ccu.constraint_name "
                , Text
"WHERE tc.constraint_type='FOREIGN KEY' "
                , Text
"AND kcu.ordinal_position=1 "
                , Text
"AND kcu.table_name=? "
                , Text
"AND kcu.column_name=? "
                , Text
"AND tc.constraint_name=?"
                ]
        Statement
stmt <- Text -> IO Statement
getter Text
sql
        [[PersistValue]]
cntrs <-
            Acquire (ConduitM () [PersistValue] IO ())
-> (ConduitM () [PersistValue] IO () -> IO [[PersistValue]])
-> IO [[PersistValue]]
forall (m :: * -> *) a b.
MonadUnliftIO m =>
Acquire a -> (a -> m b) -> m b
with
                (Statement
-> [PersistValue] -> Acquire (ConduitM () [PersistValue] IO ())
Statement
-> forall (m :: * -> *).
   MonadIO m =>
   [PersistValue] -> Acquire (ConduitM () [PersistValue] m ())
stmtQuery Statement
stmt
                    [ Text -> PersistValue
PersistText (Text -> PersistValue) -> Text -> PersistValue
forall a b. (a -> b) -> a -> b
$ EntityNameDB -> Text
unEntityNameDB EntityNameDB
tableName'
                    , Text -> PersistValue
PersistText (Text -> PersistValue) -> Text -> PersistValue
forall a b. (a -> b) -> a -> b
$ FieldNameDB -> Text
unFieldNameDB FieldNameDB
cname
                    , Text -> PersistValue
PersistText (Text -> PersistValue) -> Text -> PersistValue
forall a b. (a -> b) -> a -> b
$ ConstraintNameDB -> Text
unConstraintNameDB ConstraintNameDB
refName'
                    ]
                )
                (\ConduitM () [PersistValue] IO ()
src -> ConduitT () Void IO [[PersistValue]] -> IO [[PersistValue]]
forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit (ConduitT () Void IO [[PersistValue]] -> IO [[PersistValue]])
-> ConduitT () Void IO [[PersistValue]] -> IO [[PersistValue]]
forall a b. (a -> b) -> a -> b
$ ConduitM () [PersistValue] IO ()
src ConduitM () [PersistValue] IO ()
-> ConduitM [PersistValue] Void IO [[PersistValue]]
-> ConduitT () Void IO [[PersistValue]]
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.| ConduitM [PersistValue] Void IO [[PersistValue]]
forall (m :: * -> *) a o. Monad m => ConduitT a o m [a]
CL.consume)
        case [[PersistValue]]
cntrs of
          [] ->
              Maybe (EntityNameDB, ConstraintNameDB, Text, Text)
-> IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (EntityNameDB, ConstraintNameDB, Text, Text)
forall a. Maybe a
Nothing
          [[PersistText Text
table, PersistText Text
constraint, PersistText Text
updRule, PersistText Text
delRule]] ->
              Maybe (EntityNameDB, ConstraintNameDB, Text, Text)
-> IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (EntityNameDB, ConstraintNameDB, Text, Text)
 -> IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text)))
-> Maybe (EntityNameDB, ConstraintNameDB, Text, Text)
-> IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
forall a b. (a -> b) -> a -> b
$ (EntityNameDB, ConstraintNameDB, Text, Text)
-> Maybe (EntityNameDB, ConstraintNameDB, Text, Text)
forall a. a -> Maybe a
Just (Text -> EntityNameDB
EntityNameDB Text
table, Text -> ConstraintNameDB
ConstraintNameDB Text
constraint, Text
updRule, Text
delRule)
          [[PersistValue]]
xs ->
              String -> IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
forall a. HasCallStack => String -> a
error (String -> IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text)))
-> String
-> IO (Maybe (EntityNameDB, ConstraintNameDB, Text, Text))
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat
                  [ String
"Postgresql.getColumn: error fetching constraints. Expected a single result for foreign key query for table: "
                  , Text -> String
T.unpack (EntityNameDB -> Text
unEntityNameDB EntityNameDB
tableName')
                  , String
" and column: "
                  , Text -> String
T.unpack (FieldNameDB -> Text
unFieldNameDB FieldNameDB
cname)
                  , String
" but got: "
                  , [[PersistValue]] -> String
forall a. Show a => a -> String
show [[PersistValue]]
xs
                  ]

    getType :: Text -> ExceptT Text IO SqlType
getType Text
"int4"        = SqlType -> ExceptT Text IO SqlType
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlType
SqlInt32
    getType Text
"int8"        = SqlType -> ExceptT Text IO SqlType
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlType
SqlInt64
    getType Text
"varchar"     = SqlType -> ExceptT Text IO SqlType
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlType
SqlString
    getType Text
"text"        = SqlType -> ExceptT Text IO SqlType
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlType
SqlString
    getType Text
"date"        = SqlType -> ExceptT Text IO SqlType
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlType
SqlDay
    getType Text
"bool"        = SqlType -> ExceptT Text IO SqlType
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlType
SqlBool
    getType Text
"timestamptz" = SqlType -> ExceptT Text IO SqlType
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlType
SqlDayTime
    getType Text
"float4"      = SqlType -> ExceptT Text IO SqlType
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlType
SqlReal
    getType Text
"float8"      = SqlType -> ExceptT Text IO SqlType
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlType
SqlReal
    getType Text
"bytea"       = SqlType -> ExceptT Text IO SqlType
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlType
SqlBlob
    getType Text
"time"        = SqlType -> ExceptT Text IO SqlType
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlType
SqlTime
    getType Text
"numeric"     = PersistValue -> PersistValue -> ExceptT Text IO SqlType
getNumeric PersistValue
numericPrecision PersistValue
numericScale
    getType Text
a             = SqlType -> ExceptT Text IO SqlType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlType -> ExceptT Text IO SqlType)
-> SqlType -> ExceptT Text IO SqlType
forall a b. (a -> b) -> a -> b
$ Text -> SqlType
SqlOther Text
a

    getNumeric :: PersistValue -> PersistValue -> ExceptT Text IO SqlType
getNumeric (PersistInt64 Int64
a) (PersistInt64 Int64
b) =
        SqlType -> ExceptT Text IO SqlType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlType -> ExceptT Text IO SqlType)
-> SqlType -> ExceptT Text IO SqlType
forall a b. (a -> b) -> a -> b
$ Word32 -> Word32 -> SqlType
SqlNumeric (Int64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
a) (Int64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
b)

    getNumeric PersistValue
PersistNull PersistValue
PersistNull = Text -> ExceptT Text IO SqlType
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ExceptT Text IO SqlType)
-> Text -> ExceptT Text IO SqlType
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat
        [ Text
"No precision and scale were specified for the column: "
        , Text
columnName
        , Text
" in table: "
        , EntityNameDB -> Text
unEntityNameDB EntityNameDB
tableName'
        , Text
". Postgres defaults to a maximum scale of 147,455 and precision of 16383,"
        , Text
" which is probably not what you intended."
        , Text
" Specify the values as numeric(total_digits, digits_after_decimal_place)."
        ]

    getNumeric PersistValue
a PersistValue
b = Text -> ExceptT Text IO SqlType
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (Text -> ExceptT Text IO SqlType)
-> Text -> ExceptT Text IO SqlType
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat
        [ Text
"Can not get numeric field precision for the column: "
        , Text
columnName
        , Text
" in table: "
        , EntityNameDB -> Text
unEntityNameDB EntityNameDB
tableName'
        , Text
". Expected an integer for both precision and scale, "
        , Text
"got: "
        , String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ PersistValue -> String
forall a. Show a => a -> String
show PersistValue
a
        , Text
" and "
        , String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ PersistValue -> String
forall a. Show a => a -> String
show PersistValue
b
        , Text
", respectively."
        , Text
" Specify the values as numeric(total_digits, digits_after_decimal_place)."
        ]

getColumn Text -> IO Statement
_ EntityNameDB
_ [PersistValue]
columnName Maybe (EntityNameDB, ConstraintNameDB)
_ =
    Either Text Column -> IO (Either Text Column)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Text Column -> IO (Either Text Column))
-> Either Text Column -> IO (Either Text Column)
forall a b. (a -> b) -> a -> b
$ Text -> Either Text Column
forall a b. a -> Either a b
Left (Text -> Either Text Column) -> Text -> Either Text Column
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"Invalid result from information_schema: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [PersistValue] -> String
forall a. Show a => a -> String
show [PersistValue]
columnName

-- | Intelligent comparison of SQL types, to account for SqlInt32 vs SqlOther integer
sqlTypeEq :: SqlType -> SqlType -> Bool
sqlTypeEq :: SqlType -> SqlType -> Bool
sqlTypeEq SqlType
x SqlType
y =
    Text -> Text
T.toCaseFold (SqlType -> Text
showSqlType SqlType
x) Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Text
T.toCaseFold (SqlType -> Text
showSqlType SqlType
y)

findAlters
    :: [EntityDef]
    -- ^ The list of all entity definitions that persistent is aware of.
    -> EntityDef
    -- ^ The entity definition for the entity that we're working on.
    -> Column
    -- ^ The column that we're searching for potential alterations for.
    -> [Column]
    -> ([AlterColumn], [Column])
findAlters :: [EntityDef]
-> EntityDef -> Column -> [Column] -> ([AlterColumn], [Column])
findAlters [EntityDef]
defs EntityDef
edef col :: Column
col@(Column FieldNameDB
name Bool
isNull SqlType
sqltype Maybe Text
def Maybe Text
_gen Maybe ConstraintNameDB
_defConstraintName Maybe Integer
_maxLen Maybe ColumnReference
ref) [Column]
cols =
    case (Column -> Bool) -> [Column] -> Maybe Column
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
List.find (\Column
c -> Column -> FieldNameDB
cName Column
c FieldNameDB -> FieldNameDB -> Bool
forall a. Eq a => a -> a -> Bool
== FieldNameDB
name) [Column]
cols of
        Maybe Column
Nothing ->
            ([Column -> AlterColumn
Add' Column
col], [Column]
cols)
        Just (Column FieldNameDB
_oldName Bool
isNull' SqlType
sqltype' Maybe Text
def' Maybe Text
_gen' Maybe ConstraintNameDB
_defConstraintName' Maybe Integer
_maxLen' Maybe ColumnReference
ref') ->
            let refDrop :: Maybe ColumnReference -> [AlterColumn]
refDrop Maybe ColumnReference
Nothing = []
                refDrop (Just ColumnReference {crConstraintName :: ColumnReference -> ConstraintNameDB
crConstraintName=ConstraintNameDB
cname}) =
                    [ConstraintNameDB -> AlterColumn
DropReference ConstraintNameDB
cname]

                refAdd :: Maybe ColumnReference -> [AlterColumn]
refAdd Maybe ColumnReference
Nothing = []
                refAdd (Just ColumnReference
colRef) =
                    case (EntityDef -> Bool) -> [EntityDef] -> Maybe EntityDef
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((EntityNameDB -> EntityNameDB -> Bool
forall a. Eq a => a -> a -> Bool
== ColumnReference -> EntityNameDB
crTableName ColumnReference
colRef) (EntityNameDB -> Bool)
-> (EntityDef -> EntityNameDB) -> EntityDef -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntityDef -> EntityNameDB
getEntityDBName) [EntityDef]
defs of
                        Just EntityDef
refdef
                            | FieldNameDB -> Maybe FieldNameDB
forall a. a -> Maybe a
Just FieldNameDB
_oldName Maybe FieldNameDB -> Maybe FieldNameDB -> Bool
forall a. Eq a => a -> a -> Bool
/= (FieldDef -> FieldNameDB) -> Maybe FieldDef -> Maybe FieldNameDB
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FieldDef -> FieldNameDB
fieldDB (EntityDef -> Maybe FieldDef
getEntityIdField EntityDef
edef)
                            ->
                            [EntityNameDB
-> ConstraintNameDB
-> [FieldNameDB]
-> [Text]
-> FieldCascade
-> AlterColumn
AddReference
                                (ColumnReference -> EntityNameDB
crTableName ColumnReference
colRef)
                                (ColumnReference -> ConstraintNameDB
crConstraintName ColumnReference
colRef)
                                [FieldNameDB
name]
                                (NonEmpty Text -> [Text]
forall a. NonEmpty a -> [a]
NEL.toList (NonEmpty Text -> [Text]) -> NonEmpty Text -> [Text]
forall a b. (a -> b) -> a -> b
$ (FieldNameDB -> Text) -> EntityDef -> NonEmpty Text
Util.dbIdColumnsEsc FieldNameDB -> Text
escapeF EntityDef
refdef)
                                (ColumnReference -> FieldCascade
crFieldCascade ColumnReference
colRef)
                            ]
                        Just EntityDef
_ -> []
                        Maybe EntityDef
Nothing ->
                            String -> [AlterColumn]
forall a. HasCallStack => String -> a
error (String -> [AlterColumn]) -> String -> [AlterColumn]
forall a b. (a -> b) -> a -> b
$ String
"could not find the entityDef for reftable["
                                String -> ShowS
forall a. [a] -> [a] -> [a]
++ EntityNameDB -> String
forall a. Show a => a -> String
show (ColumnReference -> EntityNameDB
crTableName ColumnReference
colRef) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"]"
                modRef :: [AlterColumn]
modRef =
                    if Maybe ColumnReference -> Maybe ColumnReference -> Bool
equivalentRef Maybe ColumnReference
ref Maybe ColumnReference
ref'
                        then []
                        else Maybe ColumnReference -> [AlterColumn]
refDrop Maybe ColumnReference
ref' [AlterColumn] -> [AlterColumn] -> [AlterColumn]
forall a. [a] -> [a] -> [a]
++ Maybe ColumnReference -> [AlterColumn]
refAdd Maybe ColumnReference
ref
                modNull :: [AlterColumn]
modNull = case (Bool
isNull, Bool
isNull') of
                            (Bool
True, Bool
False) ->  do
                                Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> [()]) -> Bool -> [()]
forall a b. (a -> b) -> a -> b
$ FieldNameDB -> Maybe FieldNameDB
forall a. a -> Maybe a
Just FieldNameDB
name Maybe FieldNameDB -> Maybe FieldNameDB -> Bool
forall a. Eq a => a -> a -> Bool
/= (FieldDef -> FieldNameDB) -> Maybe FieldDef -> Maybe FieldNameDB
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FieldDef -> FieldNameDB
fieldDB (EntityDef -> Maybe FieldDef
getEntityIdField EntityDef
edef)
                                AlterColumn -> [AlterColumn]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Column -> AlterColumn
IsNull Column
col)
                            (Bool
False, Bool
True) ->
                                let up :: [AlterColumn] -> [AlterColumn]
up = case Maybe Text
def of
                                            Maybe Text
Nothing -> [AlterColumn] -> [AlterColumn]
forall a. a -> a
id
                                            Just Text
s -> (:) (Column -> Text -> AlterColumn
Update' Column
col Text
s)
                                 in [AlterColumn] -> [AlterColumn]
up [Column -> AlterColumn
NotNull Column
col]
                            (Bool, Bool)
_ -> []
                modType :: [AlterColumn]
modType
                    | SqlType -> SqlType -> Bool
sqlTypeEq SqlType
sqltype SqlType
sqltype' = []
                    -- When converting from Persistent pre-2.0 databases, we
                    -- need to make sure that TIMESTAMP WITHOUT TIME ZONE is
                    -- treated as UTC.
                    | SqlType
sqltype SqlType -> SqlType -> Bool
forall a. Eq a => a -> a -> Bool
== SqlType
SqlDayTime Bool -> Bool -> Bool
&& SqlType
sqltype' SqlType -> SqlType -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> SqlType
SqlOther Text
"timestamp" =
                        [Column -> SqlType -> Text -> AlterColumn
ChangeType Column
col SqlType
sqltype (Text -> AlterColumn) -> Text -> AlterColumn
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat
                            [ Text
" USING "
                            , FieldNameDB -> Text
escapeF FieldNameDB
name
                            , Text
" AT TIME ZONE 'UTC'"
                            ]]
                    | Bool
otherwise = [Column -> SqlType -> Text -> AlterColumn
ChangeType Column
col SqlType
sqltype Text
""]
                modDef :: [AlterColumn]
modDef =
                    if Maybe Text
def Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe Text
def'
                        Bool -> Bool -> Bool
|| Maybe Text -> Bool
forall a. Maybe a -> Bool
isJust (Text -> Text -> Maybe Text
T.stripPrefix Text
"nextval" (Text -> Maybe Text) -> Maybe Text -> Maybe Text
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe Text
def')
                        then []
                        else
                            case Maybe Text
def of
                                Maybe Text
Nothing -> [Column -> AlterColumn
NoDefault Column
col]
                                Just Text
s  -> [Column -> Text -> AlterColumn
Default Column
col Text
s]
                dropSafe :: [AlterColumn]
dropSafe =
                    if EntityDef -> FieldNameDB -> Bool
safeToRemove EntityDef
edef FieldNameDB
name
                        then String -> [AlterColumn] -> [AlterColumn]
forall a. HasCallStack => String -> a
error String
"wtf" [Column -> Bool -> AlterColumn
Drop Column
col Bool
True]
                        else []
             in
                ( [AlterColumn]
modRef [AlterColumn] -> [AlterColumn] -> [AlterColumn]
forall a. [a] -> [a] -> [a]
++ [AlterColumn]
modDef [AlterColumn] -> [AlterColumn] -> [AlterColumn]
forall a. [a] -> [a] -> [a]
++ [AlterColumn]
modNull [AlterColumn] -> [AlterColumn] -> [AlterColumn]
forall a. [a] -> [a] -> [a]
++ [AlterColumn]
modType [AlterColumn] -> [AlterColumn] -> [AlterColumn]
forall a. [a] -> [a] -> [a]
++ [AlterColumn]
dropSafe
                , (Column -> Bool) -> [Column] -> [Column]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Column
c -> Column -> FieldNameDB
cName Column
c FieldNameDB -> FieldNameDB -> Bool
forall a. Eq a => a -> a -> Bool
/= FieldNameDB
name) [Column]
cols
                )

-- We check if we should alter a foreign key. This is almost an equality check,
-- except we consider 'Nothing' and 'Just Restrict' equivalent.
equivalentRef :: Maybe ColumnReference -> Maybe ColumnReference -> Bool
equivalentRef :: Maybe ColumnReference -> Maybe ColumnReference -> Bool
equivalentRef Maybe ColumnReference
Nothing Maybe ColumnReference
Nothing = Bool
True
equivalentRef (Just ColumnReference
cr1) (Just ColumnReference
cr2) =
       ColumnReference -> EntityNameDB
crTableName ColumnReference
cr1 EntityNameDB -> EntityNameDB -> Bool
forall a. Eq a => a -> a -> Bool
== ColumnReference -> EntityNameDB
crTableName ColumnReference
cr2
    Bool -> Bool -> Bool
&& ColumnReference -> ConstraintNameDB
crConstraintName ColumnReference
cr1 ConstraintNameDB -> ConstraintNameDB -> Bool
forall a. Eq a => a -> a -> Bool
== ColumnReference -> ConstraintNameDB
crConstraintName ColumnReference
cr2
    Bool -> Bool -> Bool
&& Maybe CascadeAction -> Maybe CascadeAction -> Bool
eqCascade (FieldCascade -> Maybe CascadeAction
fcOnUpdate (FieldCascade -> Maybe CascadeAction)
-> FieldCascade -> Maybe CascadeAction
forall a b. (a -> b) -> a -> b
$ ColumnReference -> FieldCascade
crFieldCascade ColumnReference
cr1) (FieldCascade -> Maybe CascadeAction
fcOnUpdate (FieldCascade -> Maybe CascadeAction)
-> FieldCascade -> Maybe CascadeAction
forall a b. (a -> b) -> a -> b
$ ColumnReference -> FieldCascade
crFieldCascade ColumnReference
cr2)
    Bool -> Bool -> Bool
&& Maybe CascadeAction -> Maybe CascadeAction -> Bool
eqCascade (FieldCascade -> Maybe CascadeAction
fcOnDelete (FieldCascade -> Maybe CascadeAction)
-> FieldCascade -> Maybe CascadeAction
forall a b. (a -> b) -> a -> b
$ ColumnReference -> FieldCascade
crFieldCascade ColumnReference
cr1) (FieldCascade -> Maybe CascadeAction
fcOnDelete (FieldCascade -> Maybe CascadeAction)
-> FieldCascade -> Maybe CascadeAction
forall a b. (a -> b) -> a -> b
$ ColumnReference -> FieldCascade
crFieldCascade ColumnReference
cr2)
  where
    eqCascade :: Maybe CascadeAction -> Maybe CascadeAction -> Bool
    eqCascade :: Maybe CascadeAction -> Maybe CascadeAction -> Bool
eqCascade Maybe CascadeAction
Nothing Maybe CascadeAction
Nothing         = Bool
True
    eqCascade Maybe CascadeAction
Nothing (Just CascadeAction
Restrict) = Bool
True
    eqCascade (Just CascadeAction
Restrict) Maybe CascadeAction
Nothing = Bool
True
    eqCascade (Just CascadeAction
cs1) (Just CascadeAction
cs2)   = CascadeAction
cs1 CascadeAction -> CascadeAction -> Bool
forall a. Eq a => a -> a -> Bool
== CascadeAction
cs2
    eqCascade Maybe CascadeAction
_ Maybe CascadeAction
_                     = Bool
False
equivalentRef Maybe ColumnReference
_ Maybe ColumnReference
_ = Bool
False

-- | Get the references to be added to a table for the given column.
getAddReference
    :: [EntityDef]
    -> EntityDef
    -> FieldNameDB
    -> ColumnReference
    -> Maybe AlterDB
getAddReference :: [EntityDef]
-> EntityDef -> FieldNameDB -> ColumnReference -> Maybe AlterDB
getAddReference [EntityDef]
allDefs EntityDef
entity FieldNameDB
cname cr :: ColumnReference
cr@ColumnReference {crTableName :: ColumnReference -> EntityNameDB
crTableName = EntityNameDB
s, crConstraintName :: ColumnReference -> ConstraintNameDB
crConstraintName=ConstraintNameDB
constraintName} = do
    Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ FieldNameDB -> Maybe FieldNameDB
forall a. a -> Maybe a
Just FieldNameDB
cname Maybe FieldNameDB -> Maybe FieldNameDB -> Bool
forall a. Eq a => a -> a -> Bool
/= (FieldDef -> FieldNameDB) -> Maybe FieldDef -> Maybe FieldNameDB
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FieldDef -> FieldNameDB
fieldDB (EntityDef -> Maybe FieldDef
getEntityIdField EntityDef
entity)
    AlterDB -> Maybe AlterDB
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AlterDB -> Maybe AlterDB) -> AlterDB -> Maybe AlterDB
forall a b. (a -> b) -> a -> b
$ EntityNameDB -> AlterColumn -> AlterDB
AlterColumn
        EntityNameDB
table
        (EntityNameDB
-> ConstraintNameDB
-> [FieldNameDB]
-> [Text]
-> FieldCascade
-> AlterColumn
AddReference EntityNameDB
s ConstraintNameDB
constraintName [FieldNameDB
cname] [Text]
id_ (ColumnReference -> FieldCascade
crFieldCascade ColumnReference
cr)
        )
  where
    table :: EntityNameDB
table = EntityDef -> EntityNameDB
getEntityDBName EntityDef
entity
    id_ :: [Text]
id_ =
        [Text] -> Maybe [Text] -> [Text]
forall a. a -> Maybe a -> a
fromMaybe
            (String -> [Text]
forall a. HasCallStack => String -> a
error (String -> [Text]) -> String -> [Text]
forall a b. (a -> b) -> a -> b
$ String
"Could not find ID of entity " String -> ShowS
forall a. [a] -> [a] -> [a]
++ EntityNameDB -> String
forall a. Show a => a -> String
show EntityNameDB
s)
            (Maybe [Text] -> [Text]) -> Maybe [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ do
                EntityDef
entDef <- (EntityDef -> Bool) -> [EntityDef] -> Maybe EntityDef
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((EntityNameDB -> EntityNameDB -> Bool
forall a. Eq a => a -> a -> Bool
== EntityNameDB
s) (EntityNameDB -> Bool)
-> (EntityDef -> EntityNameDB) -> EntityDef -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntityDef -> EntityNameDB
getEntityDBName) [EntityDef]
allDefs
                [Text] -> Maybe [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text] -> Maybe [Text]) -> [Text] -> Maybe [Text]
forall a b. (a -> b) -> a -> b
$ NonEmpty Text -> [Text]
forall a. NonEmpty a -> [a]
NEL.toList (NonEmpty Text -> [Text]) -> NonEmpty Text -> [Text]
forall a b. (a -> b) -> a -> b
$ (FieldNameDB -> Text) -> EntityDef -> NonEmpty Text
Util.dbIdColumnsEsc FieldNameDB -> Text
escapeF EntityDef
entDef

showColumn :: Column -> Text
showColumn :: Column -> Text
showColumn (Column FieldNameDB
n Bool
nu SqlType
sqlType' Maybe Text
def Maybe Text
gen Maybe ConstraintNameDB
_defConstraintName Maybe Integer
_maxLen Maybe ColumnReference
_ref) = [Text] -> Text
T.concat
    [ FieldNameDB -> Text
escapeF FieldNameDB
n
    , Text
" "
    , SqlType -> Text
showSqlType SqlType
sqlType'
    , Text
" "
    , if Bool
nu then Text
"NULL" else Text
"NOT NULL"
    , case Maybe Text
def of
        Maybe Text
Nothing -> Text
""
        Just Text
s -> Text
" DEFAULT " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s
    , case Maybe Text
gen of
        Maybe Text
Nothing -> Text
""
        Just Text
s -> Text
" GENERATED ALWAYS AS (" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
") STORED"
    ]

showSqlType :: SqlType -> Text
showSqlType :: SqlType -> Text
showSqlType SqlType
SqlString = Text
"VARCHAR"
showSqlType SqlType
SqlInt32 = Text
"INT4"
showSqlType SqlType
SqlInt64 = Text
"INT8"
showSqlType SqlType
SqlReal = Text
"DOUBLE PRECISION"
showSqlType (SqlNumeric Word32
s Word32
prec) = [Text] -> Text
T.concat [ Text
"NUMERIC(", String -> Text
T.pack (Word32 -> String
forall a. Show a => a -> String
show Word32
s), Text
",", String -> Text
T.pack (Word32 -> String
forall a. Show a => a -> String
show Word32
prec), Text
")" ]
showSqlType SqlType
SqlDay = Text
"DATE"
showSqlType SqlType
SqlTime = Text
"TIME"
showSqlType SqlType
SqlDayTime = Text
"TIMESTAMP WITH TIME ZONE"
showSqlType SqlType
SqlBlob = Text
"BYTEA"
showSqlType SqlType
SqlBool = Text
"BOOLEAN"

-- Added for aliasing issues re: https://github.com/yesodweb/yesod/issues/682
showSqlType (SqlOther (Text -> Text
T.toLower -> Text
"integer")) = Text
"INT4"

showSqlType (SqlOther Text
t) = Text
t

showAlterDb :: AlterDB -> (Bool, Text)
showAlterDb :: AlterDB -> (Bool, Text)
showAlterDb (AddTable Text
s) = (Bool
False, Text
s)
showAlterDb (AlterColumn EntityNameDB
t AlterColumn
ac) =
    (AlterColumn -> Bool
isUnsafe AlterColumn
ac, EntityNameDB -> AlterColumn -> Text
showAlter EntityNameDB
t AlterColumn
ac)
  where
    isUnsafe :: AlterColumn -> Bool
isUnsafe (Drop Column
_ Bool
safeRemove) = Bool -> Bool
not Bool
safeRemove
    isUnsafe AlterColumn
_ = Bool
False
showAlterDb (AlterTable EntityNameDB
t AlterTable
at) = (Bool
False, EntityNameDB -> AlterTable -> Text
showAlterTable EntityNameDB
t AlterTable
at)

showAlterTable :: EntityNameDB -> AlterTable -> Text
showAlterTable :: EntityNameDB -> AlterTable -> Text
showAlterTable EntityNameDB
table (AddUniqueConstraint ConstraintNameDB
cname [FieldNameDB]
cols) = [Text] -> Text
T.concat
    [ Text
"ALTER TABLE "
    , EntityNameDB -> Text
escapeE EntityNameDB
table
    , Text
" ADD CONSTRAINT "
    , ConstraintNameDB -> Text
escapeC ConstraintNameDB
cname
    , Text
" UNIQUE("
    , Text -> [Text] -> Text
T.intercalate Text
"," ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (FieldNameDB -> Text) -> [FieldNameDB] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map FieldNameDB -> Text
escapeF [FieldNameDB]
cols
    , Text
")"
    ]
showAlterTable EntityNameDB
table (DropConstraint ConstraintNameDB
cname) = [Text] -> Text
T.concat
    [ Text
"ALTER TABLE "
    , EntityNameDB -> Text
escapeE EntityNameDB
table
    , Text
" DROP CONSTRAINT "
    , ConstraintNameDB -> Text
escapeC ConstraintNameDB
cname
    ]

showAlter :: EntityNameDB -> AlterColumn -> Text
showAlter :: EntityNameDB -> AlterColumn -> Text
showAlter EntityNameDB
table (ChangeType Column
c SqlType
t Text
extra) =
    [Text] -> Text
T.concat
        [ Text
"ALTER TABLE "
        , EntityNameDB -> Text
escapeE EntityNameDB
table
        , Text
" ALTER COLUMN "
        , FieldNameDB -> Text
escapeF (Column -> FieldNameDB
cName Column
c)
        , Text
" TYPE "
        , SqlType -> Text
showSqlType SqlType
t
        , Text
extra
        ]
showAlter EntityNameDB
table (IsNull Column
c) =
    [Text] -> Text
T.concat
        [ Text
"ALTER TABLE "
        , EntityNameDB -> Text
escapeE EntityNameDB
table
        , Text
" ALTER COLUMN "
        , FieldNameDB -> Text
escapeF (Column -> FieldNameDB
cName Column
c)
        , Text
" DROP NOT NULL"
        ]
showAlter EntityNameDB
table (NotNull Column
c) =
    [Text] -> Text
T.concat
        [ Text
"ALTER TABLE "
        , EntityNameDB -> Text
escapeE EntityNameDB
table
        , Text
" ALTER COLUMN "
        , FieldNameDB -> Text
escapeF (Column -> FieldNameDB
cName Column
c)
        , Text
" SET NOT NULL"
        ]
showAlter EntityNameDB
table (Add' Column
col) =
    [Text] -> Text
T.concat
        [ Text
"ALTER TABLE "
        , EntityNameDB -> Text
escapeE EntityNameDB
table
        , Text
" ADD COLUMN "
        , Column -> Text
showColumn Column
col
        ]
showAlter EntityNameDB
table (Drop Column
c Bool
_) =
    [Text] -> Text
T.concat
        [ Text
"ALTER TABLE "
        , EntityNameDB -> Text
escapeE EntityNameDB
table
        , Text
" DROP COLUMN "
        , FieldNameDB -> Text
escapeF (Column -> FieldNameDB
cName Column
c)
        ]
showAlter EntityNameDB
table (Default Column
c Text
s) =
    [Text] -> Text
T.concat
        [ Text
"ALTER TABLE "
        , EntityNameDB -> Text
escapeE EntityNameDB
table
        , Text
" ALTER COLUMN "
        , FieldNameDB -> Text
escapeF (Column -> FieldNameDB
cName Column
c)
        , Text
" SET DEFAULT "
        , Text
s
        ]
showAlter EntityNameDB
table (NoDefault Column
c) = [Text] -> Text
T.concat
    [ Text
"ALTER TABLE "
    , EntityNameDB -> Text
escapeE EntityNameDB
table
    , Text
" ALTER COLUMN "
    , FieldNameDB -> Text
escapeF (Column -> FieldNameDB
cName Column
c)
    , Text
" DROP DEFAULT"
    ]
showAlter EntityNameDB
table (Update' Column
c Text
s) = [Text] -> Text
T.concat
    [ Text
"UPDATE "
    , EntityNameDB -> Text
escapeE EntityNameDB
table
    , Text
" SET "
    , FieldNameDB -> Text
escapeF (Column -> FieldNameDB
cName Column
c)
    , Text
"="
    , Text
s
    , Text
" WHERE "
    , FieldNameDB -> Text
escapeF (Column -> FieldNameDB
cName Column
c)
    , Text
" IS NULL"
    ]
showAlter EntityNameDB
table (AddReference EntityNameDB
reftable ConstraintNameDB
fkeyname [FieldNameDB]
t2 [Text]
id2 FieldCascade
cascade) = [Text] -> Text
T.concat
    [ Text
"ALTER TABLE "
    , EntityNameDB -> Text
escapeE EntityNameDB
table
    , Text
" ADD CONSTRAINT "
    , ConstraintNameDB -> Text
escapeC ConstraintNameDB
fkeyname
    , Text
" FOREIGN KEY("
    , Text -> [Text] -> Text
T.intercalate Text
"," ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (FieldNameDB -> Text) -> [FieldNameDB] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map FieldNameDB -> Text
escapeF [FieldNameDB]
t2
    , Text
") REFERENCES "
    , EntityNameDB -> Text
escapeE EntityNameDB
reftable
    , Text
"("
    , Text -> [Text] -> Text
T.intercalate Text
"," [Text]
id2
    , Text
")"
    ] Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FieldCascade -> Text
renderFieldCascade FieldCascade
cascade
showAlter EntityNameDB
table (DropReference ConstraintNameDB
cname) = [Text] -> Text
T.concat
    [ Text
"ALTER TABLE "
    , EntityNameDB -> Text
escapeE EntityNameDB
table
    , Text
" DROP CONSTRAINT "
    , ConstraintNameDB -> Text
escapeC ConstraintNameDB
cname
    ]

-- | Get the SQL string for the table that a PeristEntity represents.
-- Useful for raw SQL queries.
tableName :: (PersistEntity record) => record -> Text
tableName :: record -> Text
tableName = EntityNameDB -> Text
escapeE (EntityNameDB -> Text)
-> (record -> EntityNameDB) -> record -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. record -> EntityNameDB
forall record. PersistEntity record => record -> EntityNameDB
tableDBName

-- | Get the SQL string for the field that an EntityField represents.
-- Useful for raw SQL queries.
fieldName :: (PersistEntity record) => EntityField record typ -> Text
fieldName :: EntityField record typ -> Text
fieldName = FieldNameDB -> Text
escapeF (FieldNameDB -> Text)
-> (EntityField record typ -> FieldNameDB)
-> EntityField record typ
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntityField record typ -> FieldNameDB
forall record typ.
PersistEntity record =>
EntityField record typ -> FieldNameDB
fieldDBName

escapeC :: ConstraintNameDB -> Text
escapeC :: ConstraintNameDB -> Text
escapeC = (Text -> Text) -> ConstraintNameDB -> Text
forall a str. DatabaseName a => (Text -> str) -> a -> str
escapeWith Text -> Text
escape

escapeE :: EntityNameDB -> Text
escapeE :: EntityNameDB -> Text
escapeE = (Text -> Text) -> EntityNameDB -> Text
forall a str. DatabaseName a => (Text -> str) -> a -> str
escapeWith Text -> Text
escape

escapeF :: FieldNameDB -> Text
escapeF :: FieldNameDB -> Text
escapeF = (Text -> Text) -> FieldNameDB -> Text
forall a str. DatabaseName a => (Text -> str) -> a -> str
escapeWith Text -> Text
escape


escape :: Text -> Text
escape :: Text -> Text
escape Text
s =
    String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Char
'"' Char -> ShowS
forall a. a -> [a] -> [a]
: ShowS
go (Text -> String
T.unpack Text
s) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\""
  where
    go :: ShowS
go String
"" = String
""
    go (Char
'"':String
xs) = String
"\"\"" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
go String
xs
    go (Char
x:String
xs) = Char
x Char -> ShowS
forall a. a -> [a] -> [a]
: ShowS
go String
xs

-- | Information required to connect to a PostgreSQL database
-- using @persistent@'s generic facilities.  These values are the
-- same that are given to 'withPostgresqlPool'.
data PostgresConf = PostgresConf
    { PostgresConf -> ConnectionString
pgConnStr  :: ConnectionString
      -- ^ The connection string.

    -- TODO: Currently stripes, idle timeout, and pool size are all separate fields
    -- When Persistent next does a large breaking release (3.0?), we should consider making these just a single ConnectionPoolConfig value
    --
    -- Currently there the idle timeout is an Integer, rather than resource-pool's NominalDiffTime type.
    -- This is because the time package only recently added the Read instance for NominalDiffTime.
    -- Future TODO: Consider removing the Read instance, and/or making the idle timeout a NominalDiffTime.

    , PostgresConf -> Int
pgPoolStripes :: Int
    -- ^ How many stripes to divide the pool into. See "Data.Pool" for details.
    -- @since 2.11.0.0
    , PostgresConf -> Integer
pgPoolIdleTimeout :: Integer -- Ideally this would be a NominalDiffTime, but that type lacks a Read instance https://github.com/haskell/time/issues/130
    -- ^ How long connections can remain idle before being disposed of, in seconds.
    -- @since 2.11.0.0
    , PostgresConf -> Int
pgPoolSize :: Int
      -- ^ How many connections should be held in the connection pool.
    } deriving (Int -> PostgresConf -> ShowS
[PostgresConf] -> ShowS
PostgresConf -> String
(Int -> PostgresConf -> ShowS)
-> (PostgresConf -> String)
-> ([PostgresConf] -> ShowS)
-> Show PostgresConf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostgresConf] -> ShowS
$cshowList :: [PostgresConf] -> ShowS
show :: PostgresConf -> String
$cshow :: PostgresConf -> String
showsPrec :: Int -> PostgresConf -> ShowS
$cshowsPrec :: Int -> PostgresConf -> ShowS
Show, ReadPrec [PostgresConf]
ReadPrec PostgresConf
Int -> ReadS PostgresConf
ReadS [PostgresConf]
(Int -> ReadS PostgresConf)
-> ReadS [PostgresConf]
-> ReadPrec PostgresConf
-> ReadPrec [PostgresConf]
-> Read PostgresConf
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PostgresConf]
$creadListPrec :: ReadPrec [PostgresConf]
readPrec :: ReadPrec PostgresConf
$creadPrec :: ReadPrec PostgresConf
readList :: ReadS [PostgresConf]
$creadList :: ReadS [PostgresConf]
readsPrec :: Int -> ReadS PostgresConf
$creadsPrec :: Int -> ReadS PostgresConf
Read, Typeable PostgresConf
DataType
Constr
Typeable PostgresConf
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> PostgresConf -> c PostgresConf)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c PostgresConf)
-> (PostgresConf -> Constr)
-> (PostgresConf -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c PostgresConf))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c PostgresConf))
-> ((forall b. Data b => b -> b) -> PostgresConf -> PostgresConf)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> PostgresConf -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> PostgresConf -> r)
-> (forall u. (forall d. Data d => d -> u) -> PostgresConf -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> PostgresConf -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> PostgresConf -> m PostgresConf)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> PostgresConf -> m PostgresConf)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> PostgresConf -> m PostgresConf)
-> Data PostgresConf
PostgresConf -> DataType
PostgresConf -> Constr
(forall b. Data b => b -> b) -> PostgresConf -> PostgresConf
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PostgresConf -> c PostgresConf
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PostgresConf
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> PostgresConf -> u
forall u. (forall d. Data d => d -> u) -> PostgresConf -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PostgresConf -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PostgresConf -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PostgresConf -> m PostgresConf
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PostgresConf -> m PostgresConf
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PostgresConf
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PostgresConf -> c PostgresConf
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PostgresConf)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PostgresConf)
$cPostgresConf :: Constr
$tPostgresConf :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> PostgresConf -> m PostgresConf
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PostgresConf -> m PostgresConf
gmapMp :: (forall d. Data d => d -> m d) -> PostgresConf -> m PostgresConf
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PostgresConf -> m PostgresConf
gmapM :: (forall d. Data d => d -> m d) -> PostgresConf -> m PostgresConf
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PostgresConf -> m PostgresConf
gmapQi :: Int -> (forall d. Data d => d -> u) -> PostgresConf -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PostgresConf -> u
gmapQ :: (forall d. Data d => d -> u) -> PostgresConf -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PostgresConf -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PostgresConf -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PostgresConf -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PostgresConf -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PostgresConf -> r
gmapT :: (forall b. Data b => b -> b) -> PostgresConf -> PostgresConf
$cgmapT :: (forall b. Data b => b -> b) -> PostgresConf -> PostgresConf
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PostgresConf)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PostgresConf)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c PostgresConf)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PostgresConf)
dataTypeOf :: PostgresConf -> DataType
$cdataTypeOf :: PostgresConf -> DataType
toConstr :: PostgresConf -> Constr
$ctoConstr :: PostgresConf -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PostgresConf
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PostgresConf
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PostgresConf -> c PostgresConf
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PostgresConf -> c PostgresConf
$cp1Data :: Typeable PostgresConf
Data)

instance FromJSON PostgresConf where
    parseJSON :: Value -> Parser PostgresConf
parseJSON Value
v = ShowS -> Parser PostgresConf -> Parser PostgresConf
forall a. ShowS -> Parser a -> Parser a
modifyFailure (String
"Persistent: error loading PostgreSQL conf: " String -> ShowS
forall a. [a] -> [a] -> [a]
++) (Parser PostgresConf -> Parser PostgresConf)
-> Parser PostgresConf -> Parser PostgresConf
forall a b. (a -> b) -> a -> b
$
      ((Object -> Parser PostgresConf) -> Value -> Parser PostgresConf)
-> Value -> (Object -> Parser PostgresConf) -> Parser PostgresConf
forall a b c. (a -> b -> c) -> b -> a -> c
flip (String
-> (Object -> Parser PostgresConf) -> Value -> Parser PostgresConf
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PostgresConf") Value
v ((Object -> Parser PostgresConf) -> Parser PostgresConf)
-> (Object -> Parser PostgresConf) -> Parser PostgresConf
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
        let defaultPoolConfig :: ConnectionPoolConfig
defaultPoolConfig = ConnectionPoolConfig
defaultConnectionPoolConfig
        String
database <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"database"
        String
host     <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"host"
        Word16
port     <- Object
o Object -> Key -> Parser (Maybe Word16)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"port" Parser (Maybe Word16) -> Word16 -> Parser Word16
forall a. Parser (Maybe a) -> a -> Parser a
.!= Word16
5432
        String
user     <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"user"
        String
password <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"password"
        Int
poolSize <- Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"poolsize" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= (ConnectionPoolConfig -> Int
connectionPoolConfigSize ConnectionPoolConfig
defaultPoolConfig)
        Int
poolStripes <- Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"stripes" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= (ConnectionPoolConfig -> Int
connectionPoolConfigStripes ConnectionPoolConfig
defaultPoolConfig)
        Integer
poolIdleTimeout <- Object
o Object -> Key -> Parser (Maybe Integer)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"idleTimeout" Parser (Maybe Integer) -> Integer -> Parser Integer
forall a. Parser (Maybe a) -> a -> Parser a
.!= (NominalDiffTime -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
floor (NominalDiffTime -> Integer) -> NominalDiffTime -> Integer
forall a b. (a -> b) -> a -> b
$ ConnectionPoolConfig -> NominalDiffTime
connectionPoolConfigIdleTimeout ConnectionPoolConfig
defaultPoolConfig)
        let ci :: ConnectInfo
ci = ConnectInfo :: String -> Word16 -> String -> String -> String -> ConnectInfo
PG.ConnectInfo
                   { connectHost :: String
PG.connectHost     = String
host
                   , connectPort :: Word16
PG.connectPort     = Word16
port
                   , connectUser :: String
PG.connectUser     = String
user
                   , connectPassword :: String
PG.connectPassword = String
password
                   , connectDatabase :: String
PG.connectDatabase = String
database
                   }
            cstr :: ConnectionString
cstr = ConnectInfo -> ConnectionString
PG.postgreSQLConnectionString ConnectInfo
ci
        PostgresConf -> Parser PostgresConf
forall (m :: * -> *) a. Monad m => a -> m a
return (PostgresConf -> Parser PostgresConf)
-> PostgresConf -> Parser PostgresConf
forall a b. (a -> b) -> a -> b
$ ConnectionString -> Int -> Integer -> Int -> PostgresConf
PostgresConf ConnectionString
cstr Int
poolStripes Integer
poolIdleTimeout Int
poolSize
instance PersistConfig PostgresConf where
    type PersistConfigBackend PostgresConf = SqlPersistT
    type PersistConfigPool PostgresConf = ConnectionPool
    createPoolConfig :: PostgresConf -> IO (PersistConfigPool PostgresConf)
createPoolConfig PostgresConf
conf = NoLoggingT IO (Pool SqlBackend) -> IO (Pool SqlBackend)
forall (m :: * -> *) a. NoLoggingT m a -> m a
runNoLoggingT (NoLoggingT IO (Pool SqlBackend) -> IO (Pool SqlBackend))
-> NoLoggingT IO (Pool SqlBackend) -> IO (Pool SqlBackend)
forall a b. (a -> b) -> a -> b
$ PostgresConf
-> PostgresConfHooks -> NoLoggingT IO (Pool SqlBackend)
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
PostgresConf -> PostgresConfHooks -> m (Pool SqlBackend)
createPostgresqlPoolWithConf PostgresConf
conf PostgresConfHooks
defaultPostgresConfHooks
    runPool :: PostgresConf
-> PersistConfigBackend PostgresConf m a
-> PersistConfigPool PostgresConf
-> m a
runPool PostgresConf
_ = PersistConfigBackend PostgresConf m a
-> PersistConfigPool PostgresConf -> m a
forall backend (m :: * -> *) a.
(MonadUnliftIO m, BackendCompatible SqlBackend backend) =>
ReaderT backend m a -> Pool backend -> m a
runSqlPool
    loadConfig :: Value -> Parser PostgresConf
loadConfig = Value -> Parser PostgresConf
forall a. FromJSON a => Value -> Parser a
parseJSON

    applyEnv :: PostgresConf -> IO PostgresConf
applyEnv PostgresConf
c0 = do
        [(String, String)]
env <- IO [(String, String)]
getEnvironment
        PostgresConf -> IO PostgresConf
forall (m :: * -> *) a. Monad m => a -> m a
return (PostgresConf -> IO PostgresConf)
-> PostgresConf -> IO PostgresConf
forall a b. (a -> b) -> a -> b
$ [(String, String)] -> PostgresConf -> PostgresConf
addUser [(String, String)]
env
               (PostgresConf -> PostgresConf) -> PostgresConf -> PostgresConf
forall a b. (a -> b) -> a -> b
$ [(String, String)] -> PostgresConf -> PostgresConf
addPass [(String, String)]
env
               (PostgresConf -> PostgresConf) -> PostgresConf -> PostgresConf
forall a b. (a -> b) -> a -> b
$ [(String, String)] -> PostgresConf -> PostgresConf
addDatabase [(String, String)]
env
               (PostgresConf -> PostgresConf) -> PostgresConf -> PostgresConf
forall a b. (a -> b) -> a -> b
$ [(String, String)] -> PostgresConf -> PostgresConf
addPort [(String, String)]
env
               (PostgresConf -> PostgresConf) -> PostgresConf -> PostgresConf
forall a b. (a -> b) -> a -> b
$ [(String, String)] -> PostgresConf -> PostgresConf
addHost [(String, String)]
env PostgresConf
c0
      where
        addParam :: ConnectionString -> String -> PostgresConf -> PostgresConf
addParam ConnectionString
param String
val PostgresConf
c =
            PostgresConf
c { pgConnStr :: ConnectionString
pgConnStr = [ConnectionString] -> ConnectionString
B8.concat [PostgresConf -> ConnectionString
pgConnStr PostgresConf
c, ConnectionString
" ", ConnectionString
param, ConnectionString
"='", String -> ConnectionString
pgescape String
val, ConnectionString
"'"] }

        pgescape :: String -> ConnectionString
pgescape = String -> ConnectionString
B8.pack (String -> ConnectionString) -> ShowS -> String -> ConnectionString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
go
            where
              go :: ShowS
go (Char
'\'':String
rest) = Char
'\\' Char -> ShowS
forall a. a -> [a] -> [a]
: Char
'\'' Char -> ShowS
forall a. a -> [a] -> [a]
: ShowS
go String
rest
              go (Char
'\\':String
rest) = Char
'\\' Char -> ShowS
forall a. a -> [a] -> [a]
: Char
'\\' Char -> ShowS
forall a. a -> [a] -> [a]
: ShowS
go String
rest
              go ( Char
x  :String
rest) =      Char
x      Char -> ShowS
forall a. a -> [a] -> [a]
: ShowS
go String
rest
              go []          = []

        maybeAddParam :: ConnectionString
-> a -> [(a, String)] -> PostgresConf -> PostgresConf
maybeAddParam ConnectionString
param a
envvar [(a, String)]
env =
            (PostgresConf -> PostgresConf)
-> (String -> PostgresConf -> PostgresConf)
-> Maybe String
-> PostgresConf
-> PostgresConf
forall b a. b -> (a -> b) -> Maybe a -> b
maybe PostgresConf -> PostgresConf
forall a. a -> a
id (ConnectionString -> String -> PostgresConf -> PostgresConf
addParam ConnectionString
param) (Maybe String -> PostgresConf -> PostgresConf)
-> Maybe String -> PostgresConf -> PostgresConf
forall a b. (a -> b) -> a -> b
$
            a -> [(a, String)] -> Maybe String
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup a
envvar [(a, String)]
env

        addHost :: [(String, String)] -> PostgresConf -> PostgresConf
addHost     = ConnectionString
-> String -> [(String, String)] -> PostgresConf -> PostgresConf
forall a.
Eq a =>
ConnectionString
-> a -> [(a, String)] -> PostgresConf -> PostgresConf
maybeAddParam ConnectionString
"host"     String
"PGHOST"
        addPort :: [(String, String)] -> PostgresConf -> PostgresConf
addPort     = ConnectionString
-> String -> [(String, String)] -> PostgresConf -> PostgresConf
forall a.
Eq a =>
ConnectionString
-> a -> [(a, String)] -> PostgresConf -> PostgresConf
maybeAddParam ConnectionString
"port"     String
"PGPORT"
        addUser :: [(String, String)] -> PostgresConf -> PostgresConf
addUser     = ConnectionString
-> String -> [(String, String)] -> PostgresConf -> PostgresConf
forall a.
Eq a =>
ConnectionString
-> a -> [(a, String)] -> PostgresConf -> PostgresConf
maybeAddParam ConnectionString
"user"     String
"PGUSER"
        addPass :: [(String, String)] -> PostgresConf -> PostgresConf
addPass     = ConnectionString
-> String -> [(String, String)] -> PostgresConf -> PostgresConf
forall a.
Eq a =>
ConnectionString
-> a -> [(a, String)] -> PostgresConf -> PostgresConf
maybeAddParam ConnectionString
"password" String
"PGPASS"
        addDatabase :: [(String, String)] -> PostgresConf -> PostgresConf
addDatabase = ConnectionString
-> String -> [(String, String)] -> PostgresConf -> PostgresConf
forall a.
Eq a =>
ConnectionString
-> a -> [(a, String)] -> PostgresConf -> PostgresConf
maybeAddParam ConnectionString
"dbname"   String
"PGDATABASE"

-- | Hooks for configuring the Persistent/its connection to Postgres
--
-- @since 2.11.0
data PostgresConfHooks = PostgresConfHooks
  { PostgresConfHooks -> Connection -> IO (NonEmpty Word)
pgConfHooksGetServerVersion :: PG.Connection -> IO (NonEmpty Word)
      -- ^ Function to get the version of Postgres
      --
      -- The default implementation queries the server with "show server_version".
      -- Some variants of Postgres, such as Redshift, don't support showing the version.
      -- It's recommended you return a hardcoded version in those cases.
      --
      -- @since 2.11.0
  , PostgresConfHooks -> Connection -> IO ()
pgConfHooksAfterCreate :: PG.Connection -> IO ()
      -- ^ Action to perform after a connection is created.
      --
      -- Typical uses of this are modifying the connection (e.g. to set the schema) or logging a connection being created.
      --
      -- The default implementation does nothing.
      --
      -- @since 2.11.0
  }

-- | Default settings for 'PostgresConfHooks'. See the individual fields of 'PostgresConfHooks' for the default values.
--
-- @since 2.11.0
defaultPostgresConfHooks :: PostgresConfHooks
defaultPostgresConfHooks :: PostgresConfHooks
defaultPostgresConfHooks = PostgresConfHooks :: (Connection -> IO (NonEmpty Word))
-> (Connection -> IO ()) -> PostgresConfHooks
PostgresConfHooks
  { pgConfHooksGetServerVersion :: Connection -> IO (NonEmpty Word)
pgConfHooksGetServerVersion = Connection -> IO (NonEmpty Word)
getServerVersionNonEmpty
  , pgConfHooksAfterCreate :: Connection -> IO ()
pgConfHooksAfterCreate = IO () -> Connection -> IO ()
forall a b. a -> b -> a
const (IO () -> Connection -> IO ()) -> IO () -> Connection -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
  }


refName :: EntityNameDB -> FieldNameDB -> ConstraintNameDB
refName :: EntityNameDB -> FieldNameDB -> ConstraintNameDB
refName (EntityNameDB Text
table) (FieldNameDB Text
column) =
    let overhead :: Int
overhead = Text -> Int
T.length (Text -> Int) -> Text -> Int
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [Text
"_", Text
"_fkey"]
        (Int
fromTable, Int
fromColumn) = Int -> (Int, Int) -> (Int, Int)
shortenNames Int
overhead (Text -> Int
T.length Text
table, Text -> Int
T.length Text
column)
    in Text -> ConstraintNameDB
ConstraintNameDB (Text -> ConstraintNameDB) -> Text -> ConstraintNameDB
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [Int -> Text -> Text
T.take Int
fromTable Text
table, Text
"_", Int -> Text -> Text
T.take Int
fromColumn Text
column, Text
"_fkey"]

    where

      -- Postgres automatically truncates too long foreign keys to a combination of
      -- truncatedTableName + "_" + truncatedColumnName + "_fkey"
      -- This works fine for normal use cases, but it creates an issue for Persistent
      -- Because after running the migrations, Persistent sees the truncated foreign key constraint
      -- doesn't have the expected name, and suggests that you migrate again
      -- To workaround this, we copy the Postgres truncation approach before sending foreign key constraints to it.
      --
      -- I believe this will also be an issue for extremely long table names,
      -- but it's just much more likely to exist with foreign key constraints because they're usually tablename * 2 in length

      -- Approximation of the algorithm Postgres uses to truncate identifiers
      -- See makeObjectName https://github.com/postgres/postgres/blob/5406513e997f5ee9de79d4076ae91c04af0c52f6/src/backend/commands/indexcmds.c#L2074-L2080
      shortenNames :: Int -> (Int, Int) -> (Int, Int)
      shortenNames :: Int -> (Int, Int) -> (Int, Int)
shortenNames Int
overhead (Int
x, Int
y)
           | Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
y Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
overhead Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
maximumIdentifierLength = (Int
x, Int
y)
           | Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
y = Int -> (Int, Int) -> (Int, Int)
shortenNames Int
overhead (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1, Int
y)
           | Bool
otherwise = Int -> (Int, Int) -> (Int, Int)
shortenNames Int
overhead (Int
x, Int
y Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)

-- | Postgres' default maximum identifier length in bytes
-- (You can re-compile Postgres with a new limit, but I'm assuming that virtually noone does this).
-- See https://www.postgresql.org/docs/11/sql-syntax-lexical.html#SQL-SYNTAX-IDENTIFIERS
maximumIdentifierLength :: Int
maximumIdentifierLength :: Int
maximumIdentifierLength = Int
63

udToPair :: UniqueDef -> (ConstraintNameDB, [FieldNameDB])
udToPair :: UniqueDef -> (ConstraintNameDB, [FieldNameDB])
udToPair UniqueDef
ud = (UniqueDef -> ConstraintNameDB
uniqueDBName UniqueDef
ud, ((FieldNameHS, FieldNameDB) -> FieldNameDB)
-> [(FieldNameHS, FieldNameDB)] -> [FieldNameDB]
forall a b. (a -> b) -> [a] -> [b]
map (FieldNameHS, FieldNameDB) -> FieldNameDB
forall a b. (a, b) -> b
snd ([(FieldNameHS, FieldNameDB)] -> [FieldNameDB])
-> [(FieldNameHS, FieldNameDB)] -> [FieldNameDB]
forall a b. (a -> b) -> a -> b
$ NonEmpty (FieldNameHS, FieldNameDB) -> [(FieldNameHS, FieldNameDB)]
forall a. NonEmpty a -> [a]
NEL.toList (NonEmpty (FieldNameHS, FieldNameDB)
 -> [(FieldNameHS, FieldNameDB)])
-> NonEmpty (FieldNameHS, FieldNameDB)
-> [(FieldNameHS, FieldNameDB)]
forall a b. (a -> b) -> a -> b
$ UniqueDef -> NonEmpty (FieldNameHS, FieldNameDB)
uniqueFields UniqueDef
ud)

mockMigrate :: [EntityDef]
         -> (Text -> IO Statement)
         -> EntityDef
         -> IO (Either [Text] [(Bool, Text)])
mockMigrate :: [EntityDef]
-> (Text -> IO Statement)
-> EntityDef
-> IO (Either [Text] [(Bool, Text)])
mockMigrate [EntityDef]
allDefs Text -> IO Statement
_ EntityDef
entity = (Either [Text] [AlterDB] -> Either [Text] [(Bool, Text)])
-> IO (Either [Text] [AlterDB])
-> IO (Either [Text] [(Bool, Text)])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([AlterDB] -> [(Bool, Text)])
-> Either [Text] [AlterDB] -> Either [Text] [(Bool, Text)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([AlterDB] -> [(Bool, Text)])
 -> Either [Text] [AlterDB] -> Either [Text] [(Bool, Text)])
-> ([AlterDB] -> [(Bool, Text)])
-> Either [Text] [AlterDB]
-> Either [Text] [(Bool, Text)]
forall a b. (a -> b) -> a -> b
$ (AlterDB -> (Bool, Text)) -> [AlterDB] -> [(Bool, Text)]
forall a b. (a -> b) -> [a] -> [b]
map AlterDB -> (Bool, Text)
showAlterDb) (IO (Either [Text] [AlterDB]) -> IO (Either [Text] [(Bool, Text)]))
-> IO (Either [Text] [AlterDB])
-> IO (Either [Text] [(Bool, Text)])
forall a b. (a -> b) -> a -> b
$ do
    case [Either Text (Either Column (ConstraintNameDB, [FieldNameDB]))]
-> ([Text], [Either Column (ConstraintNameDB, [FieldNameDB])])
forall a b. [Either a b] -> ([a], [b])
partitionEithers [] of
        ([], [Either Column (ConstraintNameDB, [FieldNameDB])]
old'') -> Either [Text] [AlterDB] -> IO (Either [Text] [AlterDB])
forall (m :: * -> *) a. Monad m => a -> m a
return (Either [Text] [AlterDB] -> IO (Either [Text] [AlterDB]))
-> Either [Text] [AlterDB] -> IO (Either [Text] [AlterDB])
forall a b. (a -> b) -> a -> b
$ [AlterDB] -> Either [Text] [AlterDB]
forall a b. b -> Either a b
Right ([AlterDB] -> Either [Text] [AlterDB])
-> [AlterDB] -> Either [Text] [AlterDB]
forall a b. (a -> b) -> a -> b
$ Bool
-> [Either Column (ConstraintNameDB, [FieldNameDB])] -> [AlterDB]
migrationText Bool
False [Either Column (ConstraintNameDB, [FieldNameDB])]
old''
        ([Text]
errs, [Either Column (ConstraintNameDB, [FieldNameDB])]
_) -> Either [Text] [AlterDB] -> IO (Either [Text] [AlterDB])
forall (m :: * -> *) a. Monad m => a -> m a
return (Either [Text] [AlterDB] -> IO (Either [Text] [AlterDB]))
-> Either [Text] [AlterDB] -> IO (Either [Text] [AlterDB])
forall a b. (a -> b) -> a -> b
$ [Text] -> Either [Text] [AlterDB]
forall a b. a -> Either a b
Left [Text]
errs
  where
    name :: EntityNameDB
name = EntityDef -> EntityNameDB
getEntityDBName EntityDef
entity
    migrationText :: Bool
-> [Either Column (ConstraintNameDB, [FieldNameDB])] -> [AlterDB]
migrationText Bool
exists' [Either Column (ConstraintNameDB, [FieldNameDB])]
old'' =
        if Bool -> Bool
not Bool
exists'
            then [Column]
-> [ForeignDef] -> [(ConstraintNameDB, [FieldNameDB])] -> [AlterDB]
createText [Column]
newcols [ForeignDef]
fdefs [(ConstraintNameDB, [FieldNameDB])]
udspair
            else let ([AlterColumn]
acs, [AlterTable]
ats) = [EntityDef]
-> EntityDef
-> ([Column], [(ConstraintNameDB, [FieldNameDB])])
-> ([Column], [(ConstraintNameDB, [FieldNameDB])])
-> ([AlterColumn], [AlterTable])
getAlters [EntityDef]
allDefs EntityDef
entity ([Column]
newcols, [(ConstraintNameDB, [FieldNameDB])]
udspair) ([Column], [(ConstraintNameDB, [FieldNameDB])])
old'
                     acs' :: [AlterDB]
acs' = (AlterColumn -> AlterDB) -> [AlterColumn] -> [AlterDB]
forall a b. (a -> b) -> [a] -> [b]
map (EntityNameDB -> AlterColumn -> AlterDB
AlterColumn EntityNameDB
name) [AlterColumn]
acs
                     ats' :: [AlterDB]
ats' = (AlterTable -> AlterDB) -> [AlterTable] -> [AlterDB]
forall a b. (a -> b) -> [a] -> [b]
map (EntityNameDB -> AlterTable -> AlterDB
AlterTable EntityNameDB
name) [AlterTable]
ats
                 in  [AlterDB]
acs' [AlterDB] -> [AlterDB] -> [AlterDB]
forall a. [a] -> [a] -> [a]
++ [AlterDB]
ats'
       where
         old' :: ([Column], [(ConstraintNameDB, [FieldNameDB])])
old' = [Either Column (ConstraintNameDB, [FieldNameDB])]
-> ([Column], [(ConstraintNameDB, [FieldNameDB])])
forall a b. [Either a b] -> ([a], [b])
partitionEithers [Either Column (ConstraintNameDB, [FieldNameDB])]
old''
         ([Column]
newcols', [UniqueDef]
udefs, [ForeignDef]
fdefs) = [EntityDef] -> EntityDef -> ([Column], [UniqueDef], [ForeignDef])
postgresMkColumns [EntityDef]
allDefs EntityDef
entity
         newcols :: [Column]
newcols = (Column -> Bool) -> [Column] -> [Column]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Column -> Bool) -> Column -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntityDef -> FieldNameDB -> Bool
safeToRemove EntityDef
entity (FieldNameDB -> Bool) -> (Column -> FieldNameDB) -> Column -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Column -> FieldNameDB
cName) [Column]
newcols'
         udspair :: [(ConstraintNameDB, [FieldNameDB])]
udspair = (UniqueDef -> (ConstraintNameDB, [FieldNameDB]))
-> [UniqueDef] -> [(ConstraintNameDB, [FieldNameDB])]
forall a b. (a -> b) -> [a] -> [b]
map UniqueDef -> (ConstraintNameDB, [FieldNameDB])
udToPair [UniqueDef]
udefs
            -- Check for table existence if there are no columns, workaround
            -- for https://github.com/yesodweb/persistent/issues/152

    createText :: [Column]
-> [ForeignDef] -> [(ConstraintNameDB, [FieldNameDB])] -> [AlterDB]
createText [Column]
newcols [ForeignDef]
fdefs [(ConstraintNameDB, [FieldNameDB])]
udspair =
        ([Column] -> EntityDef -> AlterDB
addTable [Column]
newcols EntityDef
entity) AlterDB -> [AlterDB] -> [AlterDB]
forall a. a -> [a] -> [a]
: [AlterDB]
uniques [AlterDB] -> [AlterDB] -> [AlterDB]
forall a. [a] -> [a] -> [a]
++ [AlterDB]
references [AlterDB] -> [AlterDB] -> [AlterDB]
forall a. [a] -> [a] -> [a]
++ [AlterDB]
foreignsAlt
      where
        uniques :: [AlterDB]
uniques = (((ConstraintNameDB, [FieldNameDB]) -> [AlterDB])
 -> [(ConstraintNameDB, [FieldNameDB])] -> [AlterDB])
-> [(ConstraintNameDB, [FieldNameDB])]
-> ((ConstraintNameDB, [FieldNameDB]) -> [AlterDB])
-> [AlterDB]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((ConstraintNameDB, [FieldNameDB]) -> [AlterDB])
-> [(ConstraintNameDB, [FieldNameDB])] -> [AlterDB]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap [(ConstraintNameDB, [FieldNameDB])]
udspair (((ConstraintNameDB, [FieldNameDB]) -> [AlterDB]) -> [AlterDB])
-> ((ConstraintNameDB, [FieldNameDB]) -> [AlterDB]) -> [AlterDB]
forall a b. (a -> b) -> a -> b
$ \(ConstraintNameDB
uname, [FieldNameDB]
ucols) ->
                [EntityNameDB -> AlterTable -> AlterDB
AlterTable EntityNameDB
name (AlterTable -> AlterDB) -> AlterTable -> AlterDB
forall a b. (a -> b) -> a -> b
$ ConstraintNameDB -> [FieldNameDB] -> AlterTable
AddUniqueConstraint ConstraintNameDB
uname [FieldNameDB]
ucols]
        references :: [AlterDB]
references =
            (Column -> Maybe AlterDB) -> [Column] -> [AlterDB]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe
                (\Column { FieldNameDB
cName :: FieldNameDB
cName :: Column -> FieldNameDB
cName, Maybe ColumnReference
cReference :: Maybe ColumnReference
cReference :: Column -> Maybe ColumnReference
cReference } ->
                    [EntityDef]
-> EntityDef -> FieldNameDB -> ColumnReference -> Maybe AlterDB
getAddReference [EntityDef]
allDefs EntityDef
entity FieldNameDB
cName (ColumnReference -> Maybe AlterDB)
-> Maybe ColumnReference -> Maybe AlterDB
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe ColumnReference
cReference
                )
                [Column]
newcols
        foreignsAlt :: [AlterDB]
foreignsAlt = (ForeignDef -> Maybe AlterDB) -> [ForeignDef] -> [AlterDB]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (EntityDef -> ForeignDef -> Maybe AlterDB
mkForeignAlt EntityDef
entity) [ForeignDef]
fdefs

-- | Mock a migration even when the database is not present.
-- This function performs the same functionality of 'printMigration'
-- with the difference that an actual database is not needed.
mockMigration :: Migration -> IO ()
mockMigration :: Migration -> IO ()
mockMigration Migration
mig = do
    IORef (Map Text Statement)
smap <- Map Text Statement -> IO (IORef (Map Text Statement))
forall a. a -> IO (IORef a)
newIORef Map Text Statement
forall a. Monoid a => a
mempty
    let sqlbackend :: SqlBackend
sqlbackend =
            MkSqlBackendArgs -> SqlBackend
mkSqlBackend MkSqlBackendArgs :: (Text -> IO Statement)
-> (EntityDef -> [PersistValue] -> InsertSqlResult)
-> IORef (Map Text Statement)
-> IO ()
-> ([EntityDef]
    -> (Text -> IO Statement)
    -> EntityDef
    -> IO (Either [Text] [(Bool, Text)]))
-> ((Text -> IO Statement) -> Maybe IsolationLevel -> IO ())
-> ((Text -> IO Statement) -> IO ())
-> ((Text -> IO Statement) -> IO ())
-> (FieldNameDB -> Text)
-> (EntityDef -> Text)
-> (Text -> Text)
-> Text
-> Text
-> ((Int, Int) -> Text -> Text)
-> LogFunc
-> MkSqlBackendArgs
MkSqlBackendArgs
                { connPrepare :: Text -> IO Statement
connPrepare = \Text
_ -> do
                    Statement -> IO Statement
forall (m :: * -> *) a. Monad m => a -> m a
return Statement :: IO ()
-> IO ()
-> ([PersistValue] -> IO Int64)
-> (forall (m :: * -> *).
    MonadIO m =>
    [PersistValue] -> Acquire (ConduitM () [PersistValue] m ()))
-> Statement
Statement
                        { stmtFinalize :: IO ()
stmtFinalize = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
                        , stmtReset :: IO ()
stmtReset = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
                        , stmtExecute :: [PersistValue] -> IO Int64
stmtExecute = [PersistValue] -> IO Int64
forall a. HasCallStack => a
undefined
                        , stmtQuery :: forall (m :: * -> *).
MonadIO m =>
[PersistValue] -> Acquire (ConduitM () [PersistValue] m ())
stmtQuery = \[PersistValue]
_ -> ConduitM () [PersistValue] m ()
-> Acquire (ConduitM () [PersistValue] m ())
forall (m :: * -> *) a. Monad m => a -> m a
return (ConduitM () [PersistValue] m ()
 -> Acquire (ConduitM () [PersistValue] m ()))
-> ConduitM () [PersistValue] m ()
-> Acquire (ConduitM () [PersistValue] m ())
forall a b. (a -> b) -> a -> b
$ () -> ConduitM () [PersistValue] m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
                        }
                , connInsertSql :: EntityDef -> [PersistValue] -> InsertSqlResult
connInsertSql = EntityDef -> [PersistValue] -> InsertSqlResult
forall a. HasCallStack => a
undefined
                , connStmtMap :: IORef (Map Text Statement)
connStmtMap = IORef (Map Text Statement)
smap
                , connClose :: IO ()
connClose = IO ()
forall a. HasCallStack => a
undefined
                , connMigrateSql :: [EntityDef]
-> (Text -> IO Statement)
-> EntityDef
-> IO (Either [Text] [(Bool, Text)])
connMigrateSql = [EntityDef]
-> (Text -> IO Statement)
-> EntityDef
-> IO (Either [Text] [(Bool, Text)])
mockMigrate
                , connBegin :: (Text -> IO Statement) -> Maybe IsolationLevel -> IO ()
connBegin = (Text -> IO Statement) -> Maybe IsolationLevel -> IO ()
forall a. HasCallStack => a
undefined
                , connCommit :: (Text -> IO Statement) -> IO ()
connCommit = (Text -> IO Statement) -> IO ()
forall a. HasCallStack => a
undefined
                , connRollback :: (Text -> IO Statement) -> IO ()
connRollback = (Text -> IO Statement) -> IO ()
forall a. HasCallStack => a
undefined
                , connEscapeFieldName :: FieldNameDB -> Text
connEscapeFieldName = FieldNameDB -> Text
escapeF
                , connEscapeTableName :: EntityDef -> Text
connEscapeTableName = EntityNameDB -> Text
escapeE (EntityNameDB -> Text)
-> (EntityDef -> EntityNameDB) -> EntityDef -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntityDef -> EntityNameDB
getEntityDBName
                , connEscapeRawName :: Text -> Text
connEscapeRawName = Text -> Text
escape
                , connNoLimit :: Text
connNoLimit = Text
forall a. HasCallStack => a
undefined
                , connRDBMS :: Text
connRDBMS = Text
forall a. HasCallStack => a
undefined
                , connLimitOffset :: (Int, Int) -> Text -> Text
connLimitOffset = (Int, Int) -> Text -> Text
forall a. HasCallStack => a
undefined
                , connLogFunc :: LogFunc
connLogFunc = LogFunc
forall a. HasCallStack => a
undefined
                }
        result :: SqlBackend -> IO (((), [Text]), [(Bool, Text)])
result = ReaderT SqlBackend IO (((), [Text]), [(Bool, Text)])
-> SqlBackend -> IO (((), [Text]), [(Bool, Text)])
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (ReaderT SqlBackend IO (((), [Text]), [(Bool, Text)])
 -> SqlBackend -> IO (((), [Text]), [(Bool, Text)]))
-> ReaderT SqlBackend IO (((), [Text]), [(Bool, Text)])
-> SqlBackend
-> IO (((), [Text]), [(Bool, Text)])
forall a b. (a -> b) -> a -> b
$ WriterT [(Bool, Text)] (ReaderT SqlBackend IO) ((), [Text])
-> ReaderT SqlBackend IO (((), [Text]), [(Bool, Text)])
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT (WriterT [(Bool, Text)] (ReaderT SqlBackend IO) ((), [Text])
 -> ReaderT SqlBackend IO (((), [Text]), [(Bool, Text)]))
-> WriterT [(Bool, Text)] (ReaderT SqlBackend IO) ((), [Text])
-> ReaderT SqlBackend IO (((), [Text]), [(Bool, Text)])
forall a b. (a -> b) -> a -> b
$ Migration
-> WriterT [(Bool, Text)] (ReaderT SqlBackend IO) ((), [Text])
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT Migration
mig
    (((), [Text]), [(Bool, Text)])
resp <- SqlBackend -> IO (((), [Text]), [(Bool, Text)])
result SqlBackend
sqlbackend
    (Text -> IO ()) -> [Text] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Text -> IO ()
T.putStrLn ([Text] -> IO ()) -> [Text] -> IO ()
forall a b. (a -> b) -> a -> b
$ ((Bool, Text) -> Text) -> [(Bool, Text)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Bool, Text) -> Text
forall a b. (a, b) -> b
snd ([(Bool, Text)] -> [Text]) -> [(Bool, Text)] -> [Text]
forall a b. (a -> b) -> a -> b
$ (((), [Text]), [(Bool, Text)]) -> [(Bool, Text)]
forall a b. (a, b) -> b
snd (((), [Text]), [(Bool, Text)])
resp

putManySql :: EntityDef -> Int -> Text
putManySql :: EntityDef -> Int -> Text
putManySql EntityDef
ent Int
n = [Text] -> [FieldDef] -> EntityDef -> Int -> Text
putManySql' [Text]
conflictColumns [FieldDef]
fields EntityDef
ent Int
n
  where
    fields :: [FieldDef]
fields = EntityDef -> [FieldDef]
getEntityFields EntityDef
ent
    conflictColumns :: [Text]
conflictColumns = (UniqueDef -> [Text]) -> [UniqueDef] -> [Text]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (((FieldNameHS, FieldNameDB) -> Text)
-> [(FieldNameHS, FieldNameDB)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (FieldNameDB -> Text
escapeF (FieldNameDB -> Text)
-> ((FieldNameHS, FieldNameDB) -> FieldNameDB)
-> (FieldNameHS, FieldNameDB)
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FieldNameHS, FieldNameDB) -> FieldNameDB
forall a b. (a, b) -> b
snd) ([(FieldNameHS, FieldNameDB)] -> [Text])
-> (UniqueDef -> [(FieldNameHS, FieldNameDB)])
-> UniqueDef
-> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty (FieldNameHS, FieldNameDB) -> [(FieldNameHS, FieldNameDB)]
forall a. NonEmpty a -> [a]
NEL.toList (NonEmpty (FieldNameHS, FieldNameDB)
 -> [(FieldNameHS, FieldNameDB)])
-> (UniqueDef -> NonEmpty (FieldNameHS, FieldNameDB))
-> UniqueDef
-> [(FieldNameHS, FieldNameDB)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UniqueDef -> NonEmpty (FieldNameHS, FieldNameDB)
uniqueFields) (EntityDef -> [UniqueDef]
getEntityUniques EntityDef
ent)

repsertManySql :: EntityDef -> Int -> Text
repsertManySql :: EntityDef -> Int -> Text
repsertManySql EntityDef
ent Int
n = [Text] -> [FieldDef] -> EntityDef -> Int -> Text
putManySql' [Text]
conflictColumns [FieldDef]
fields EntityDef
ent Int
n
  where
    fields :: [FieldDef]
fields = NonEmpty FieldDef -> [FieldDef]
forall a. NonEmpty a -> [a]
NEL.toList (NonEmpty FieldDef -> [FieldDef])
-> NonEmpty FieldDef -> [FieldDef]
forall a b. (a -> b) -> a -> b
$ EntityDef -> NonEmpty FieldDef
keyAndEntityFields EntityDef
ent
    conflictColumns :: [Text]
conflictColumns = NonEmpty Text -> [Text]
forall a. NonEmpty a -> [a]
NEL.toList (NonEmpty Text -> [Text]) -> NonEmpty Text -> [Text]
forall a b. (a -> b) -> a -> b
$ FieldNameDB -> Text
escapeF (FieldNameDB -> Text)
-> (FieldDef -> FieldNameDB) -> FieldDef -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldDef -> FieldNameDB
fieldDB (FieldDef -> Text) -> NonEmpty FieldDef -> NonEmpty Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> EntityDef -> NonEmpty FieldDef
getEntityKeyFields EntityDef
ent

-- | This type is used to determine how to update rows using Postgres'
-- @INSERT ... ON CONFLICT KEY UPDATE@ functionality, exposed via
-- 'upsertWhere' and 'upsertManyWhere' in this library.
--
-- @since 2.12.1.0
data HandleUpdateCollision record where
  -- | Copy the field directly from the record.
  CopyField :: EntityField record typ -> HandleUpdateCollision record
  -- | Only copy the field if it is not equal to the provided value.
  CopyUnlessEq :: PersistField typ => EntityField record typ -> typ -> HandleUpdateCollision record

-- | Copy the field into the database only if the value in the
-- corresponding record is non-@NULL@.
--
-- @since  2.12.1.0
copyUnlessNull :: PersistField typ => EntityField record (Maybe typ) -> HandleUpdateCollision record
copyUnlessNull :: EntityField record (Maybe typ) -> HandleUpdateCollision record
copyUnlessNull EntityField record (Maybe typ)
field = EntityField record (Maybe typ)
-> Maybe typ -> HandleUpdateCollision record
forall typ record.
PersistField typ =>
EntityField record typ -> typ -> HandleUpdateCollision record
CopyUnlessEq EntityField record (Maybe typ)
field Maybe typ
forall a. Maybe a
Nothing

-- | Copy the field into the database only if the value in the
-- corresponding record is non-empty, where "empty" means the Monoid
-- definition for 'mempty'. Useful for 'Text', 'String', 'ByteString', etc.
--
-- The resulting 'HandleUpdateCollision' type is useful for the
-- 'upsertManyWhere' function.
--
-- @since  2.12.1.0
copyUnlessEmpty :: (Monoid.Monoid typ, PersistField typ) => EntityField record typ -> HandleUpdateCollision record
copyUnlessEmpty :: EntityField record typ -> HandleUpdateCollision record
copyUnlessEmpty EntityField record typ
field = EntityField record typ -> typ -> HandleUpdateCollision record
forall typ record.
PersistField typ =>
EntityField record typ -> typ -> HandleUpdateCollision record
CopyUnlessEq EntityField record typ
field typ
forall a. Monoid a => a
Monoid.mempty

-- | Copy the field into the database only if the field is not equal to the
-- provided value. This is useful to avoid copying weird nullary data into
-- the database.
--
-- The resulting 'HandleUpdateCollision' type is useful for the
-- 'upsertMany' function.
--
-- @since  2.12.1.0
copyUnlessEq :: PersistField typ => EntityField record typ -> typ -> HandleUpdateCollision record
copyUnlessEq :: EntityField record typ -> typ -> HandleUpdateCollision record
copyUnlessEq = EntityField record typ -> typ -> HandleUpdateCollision record
forall typ record.
PersistField typ =>
EntityField record typ -> typ -> HandleUpdateCollision record
CopyUnlessEq

-- | Copy the field directly from the record.
--
-- @since 2.12.1.0
copyField :: PersistField typ => EntityField record typ -> HandleUpdateCollision record
copyField :: EntityField record typ -> HandleUpdateCollision record
copyField = EntityField record typ -> HandleUpdateCollision record
forall record typ.
EntityField record typ -> HandleUpdateCollision record
CopyField

-- | Postgres specific 'upsertWhere'. This method does the following:
-- It will insert a record if no matching unique key exists.
-- If a unique key exists, it will update the relevant field with a user-supplied value, however,
-- it will only do this update on a user-supplied condition.
-- For example, here's how this method could be called like such:
--
-- @
-- upsertWhere record [recordField =. newValue] [recordField /= newValue]
-- @
--
-- Called thusly, this method will insert a new record (if none exists) OR update a recordField with a new value
-- assuming the condition in the last block is met.
--
-- @since 2.12.1.0
upsertWhere
  :: ( backend ~ PersistEntityBackend record
     , PersistEntity record
     , PersistEntityBackend record ~ SqlBackend
     , MonadIO m
     , PersistStore backend
     , BackendCompatible SqlBackend backend
     , OnlyOneUniqueKey record
     )
  => record
  -> [Update record]
  -> [Filter record]
  -> ReaderT backend m ()
upsertWhere :: record
-> [Update record] -> [Filter record] -> ReaderT backend m ()
upsertWhere record
record [Update record]
updates [Filter record]
filts =
  [record]
-> [HandleUpdateCollision record]
-> [Update record]
-> [Filter record]
-> ReaderT backend m ()
forall record backend (m :: * -> *).
(backend ~ PersistEntityBackend record,
 BackendCompatible SqlBackend backend,
 PersistEntityBackend record ~ SqlBackend, PersistEntity record,
 OnlyOneUniqueKey record, MonadIO m) =>
[record]
-> [HandleUpdateCollision record]
-> [Update record]
-> [Filter record]
-> ReaderT backend m ()
upsertManyWhere [record
record] [] [Update record]
updates [Filter record]
filts

-- | Postgres specific 'upsertManyWhere'. This method does the following:
-- It will insert a record if no matching unique key exists.
-- If a unique key exists, it will update the relevant field with a user-supplied value, however,
-- it will only do this update on a user-supplied condition.
-- For example, here's how this method could be called like such:
--
-- upsertManyWhere [record] [recordField =. newValue] [recordField !=. newValue]
--
-- Called thusly, this method will insert a new record (if none exists) OR update a recordField with a new value
-- assuming the condition in the last block is met.
--
-- @since 2.12.1.0
upsertManyWhere
    :: forall record backend m.
    ( backend ~ PersistEntityBackend record
    , BackendCompatible SqlBackend backend
    , PersistEntityBackend record ~ SqlBackend
    , PersistEntity record
    , OnlyOneUniqueKey record
    , MonadIO m
    )
    => [record]
    -- ^ A list of the records you want to insert, or update
    -> [HandleUpdateCollision record]
    -- ^ A list of the fields you want to copy over.
    -> [Update record]
    -- ^ A list of the updates to apply that aren't dependent on the record
    -- being inserted.
    -> [Filter record]
    -- ^ A filter condition that dictates the scope of the updates
    -> ReaderT backend m ()
upsertManyWhere :: [record]
-> [HandleUpdateCollision record]
-> [Update record]
-> [Filter record]
-> ReaderT backend m ()
upsertManyWhere [] [HandleUpdateCollision record]
_ [Update record]
_ [Filter record]
_ = () -> ReaderT backend m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
upsertManyWhere [record]
records [HandleUpdateCollision record]
fieldValues [Update record]
updates [Filter record]
filters = do
    SqlBackend
conn <- (backend -> SqlBackend) -> ReaderT backend m SqlBackend
forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks backend -> SqlBackend
forall sup sub. BackendCompatible sup sub => sub -> sup
projectBackend
    let uniqDef :: UniqueDef
uniqDef = Proxy record -> UniqueDef
forall record (proxy :: * -> *).
(OnlyOneUniqueKey record, Monad proxy) =>
proxy record -> UniqueDef
onlyOneUniqueDef (Proxy record
forall k (t :: k). Proxy t
Proxy :: Proxy record)
    (Text -> [PersistValue] -> ReaderT backend m ())
-> (Text, [PersistValue]) -> ReaderT backend m ()
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Text -> [PersistValue] -> ReaderT backend m ()
forall (m :: * -> *) backend.
(MonadIO m, BackendCompatible SqlBackend backend) =>
Text -> [PersistValue] -> ReaderT backend m ()
rawExecute ((Text, [PersistValue]) -> ReaderT backend m ())
-> (Text, [PersistValue]) -> ReaderT backend m ()
forall a b. (a -> b) -> a -> b
$
        [record]
-> SqlBackend
-> [HandleUpdateCollision record]
-> [Update record]
-> [Filter record]
-> UniqueDef
-> (Text, [PersistValue])
forall record.
(PersistEntity record, PersistEntityBackend record ~ SqlBackend,
 OnlyOneUniqueKey record) =>
[record]
-> SqlBackend
-> [HandleUpdateCollision record]
-> [Update record]
-> [Filter record]
-> UniqueDef
-> (Text, [PersistValue])
mkBulkUpsertQuery [record]
records SqlBackend
conn [HandleUpdateCollision record]
fieldValues [Update record]
updates [Filter record]
filters UniqueDef
uniqDef

-- | Exclude any record field if it doesn't match the filter record.  Used only in `upsertWhere` and
-- `upsertManyWhere`
--
-- TODO: we could probably make a sum type for the `Filter` record that's passed into the `upsertWhere` and
-- `upsertManyWhere` methods that has similar behavior to the HandleCollisionUpdate type.
--
-- @since 2.12.1.0
excludeNotEqualToOriginal
    :: (PersistField typ, PersistEntity rec)
    => EntityField rec typ
    -> Filter rec
excludeNotEqualToOriginal :: EntityField rec typ -> Filter rec
excludeNotEqualToOriginal EntityField rec typ
field =
    Filter :: forall record typ.
PersistField typ =>
EntityField record typ
-> FilterValue typ -> PersistFilter -> Filter record
Filter
        { filterField :: EntityField rec typ
filterField =
            EntityField rec typ
field
        , filterFilter :: PersistFilter
filterFilter =
            PersistFilter
Ne
        , filterValue :: FilterValue typ
filterValue =
            PersistValue -> FilterValue typ
forall a typ. PersistField a => a -> FilterValue typ
UnsafeValue (PersistValue -> FilterValue typ)
-> PersistValue -> FilterValue typ
forall a b. (a -> b) -> a -> b
$
                LiteralType -> ConnectionString -> PersistValue
PersistLiteral_
                    LiteralType
Unescaped
                    ConnectionString
bsForExcludedField
        }
  where
    bsForExcludedField :: ConnectionString
bsForExcludedField =
        Text -> ConnectionString
T.encodeUtf8
            (Text -> ConnectionString) -> Text -> ConnectionString
forall a b. (a -> b) -> a -> b
$ Text
"EXCLUDED."
            Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> EntityField rec typ -> Text
forall record typ.
PersistEntity record =>
EntityField record typ -> Text
fieldName EntityField rec typ
field

-- | This creates the query for 'upsertManyWhere'. If you
-- provide an empty list of updates to perform, then it will generate
-- a dummy/no-op update using the first field of the record. This avoids
-- duplicate key exceptions.
mkBulkUpsertQuery
    :: (PersistEntity record, PersistEntityBackend record ~ SqlBackend, OnlyOneUniqueKey record)
    => [record]
    -- ^ A list of the records you want to insert, or update
    -> SqlBackend
    -> [HandleUpdateCollision record]
    -- ^ A list of the fields you want to copy over.
    -> [Update record]
    -- ^ A list of the updates to apply that aren't dependent on the record being inserted.
    -> [Filter record]
    -- ^ A filter condition that dictates the scope of the updates
    -> UniqueDef
    -- ^ The specific uniqueness constraint to use on the record. Postgres
    -- rquires that we use exactly one relevant constraint, and it can't do
    -- a catch-all. How frustrating!
    -> (Text, [PersistValue])
mkBulkUpsertQuery :: [record]
-> SqlBackend
-> [HandleUpdateCollision record]
-> [Update record]
-> [Filter record]
-> UniqueDef
-> (Text, [PersistValue])
mkBulkUpsertQuery [record]
records SqlBackend
conn [HandleUpdateCollision record]
fieldValues [Update record]
updates [Filter record]
filters UniqueDef
uniqDef =
  (Text
q, [PersistValue]
recordValues [PersistValue] -> [PersistValue] -> [PersistValue]
forall a. Semigroup a => a -> a -> a
<> [PersistValue]
updsValues [PersistValue] -> [PersistValue] -> [PersistValue]
forall a. Semigroup a => a -> a -> a
<> [PersistValue]
copyUnlessValues [PersistValue] -> [PersistValue] -> [PersistValue]
forall a. Semigroup a => a -> a -> a
<> [PersistValue]
whereVals)
  where
    mfieldDef :: HandleUpdateCollision record -> Either (Text, PersistValue) Text
mfieldDef HandleUpdateCollision record
x = case HandleUpdateCollision record
x of
        CopyField EntityField record typ
rec -> Text -> Either (Text, PersistValue) Text
forall a b. b -> Either a b
Right (FieldDef -> Text
fieldDbToText (EntityField record typ -> FieldDef
forall record typ.
PersistEntity record =>
EntityField record typ -> FieldDef
persistFieldDef EntityField record typ
rec))
        CopyUnlessEq EntityField record typ
rec typ
val -> (Text, PersistValue) -> Either (Text, PersistValue) Text
forall a b. a -> Either a b
Left (FieldDef -> Text
fieldDbToText (EntityField record typ -> FieldDef
forall record typ.
PersistEntity record =>
EntityField record typ -> FieldDef
persistFieldDef EntityField record typ
rec), typ -> PersistValue
forall a. PersistField a => a -> PersistValue
toPersistValue typ
val)
    ([(Text, PersistValue)]
fieldsToMaybeCopy, [Text]
updateFieldNames) = [Either (Text, PersistValue) Text]
-> ([(Text, PersistValue)], [Text])
forall a b. [Either a b] -> ([a], [b])
partitionEithers ([Either (Text, PersistValue) Text]
 -> ([(Text, PersistValue)], [Text]))
-> [Either (Text, PersistValue) Text]
-> ([(Text, PersistValue)], [Text])
forall a b. (a -> b) -> a -> b
$ (HandleUpdateCollision record -> Either (Text, PersistValue) Text)
-> [HandleUpdateCollision record]
-> [Either (Text, PersistValue) Text]
forall a b. (a -> b) -> [a] -> [b]
map HandleUpdateCollision record -> Either (Text, PersistValue) Text
forall record.
PersistEntity record =>
HandleUpdateCollision record -> Either (Text, PersistValue) Text
mfieldDef [HandleUpdateCollision record]
fieldValues
    fieldDbToText :: FieldDef -> Text
fieldDbToText = FieldNameDB -> Text
escapeF (FieldNameDB -> Text)
-> (FieldDef -> FieldNameDB) -> FieldDef -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldDef -> FieldNameDB
fieldDB
    entityDef' :: EntityDef
entityDef' = [record] -> EntityDef
forall record (proxy :: * -> *).
PersistEntity record =>
proxy record -> EntityDef
entityDef [record]
records
    conflictColumns :: [Text]
conflictColumns =
        ((FieldNameHS, FieldNameDB) -> Text)
-> [(FieldNameHS, FieldNameDB)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (FieldNameDB -> Text
escapeF (FieldNameDB -> Text)
-> ((FieldNameHS, FieldNameDB) -> FieldNameDB)
-> (FieldNameHS, FieldNameDB)
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FieldNameHS, FieldNameDB) -> FieldNameDB
forall a b. (a, b) -> b
snd) ([(FieldNameHS, FieldNameDB)] -> [Text])
-> [(FieldNameHS, FieldNameDB)] -> [Text]
forall a b. (a -> b) -> a -> b
$ NonEmpty (FieldNameHS, FieldNameDB) -> [(FieldNameHS, FieldNameDB)]
forall a. NonEmpty a -> [a]
NEL.toList (NonEmpty (FieldNameHS, FieldNameDB)
 -> [(FieldNameHS, FieldNameDB)])
-> NonEmpty (FieldNameHS, FieldNameDB)
-> [(FieldNameHS, FieldNameDB)]
forall a b. (a -> b) -> a -> b
$ UniqueDef -> NonEmpty (FieldNameHS, FieldNameDB)
uniqueFields UniqueDef
uniqDef
    firstField :: Text
firstField = case [Text]
entityFieldNames of
        [] -> String -> Text
forall a. HasCallStack => String -> a
error String
"The entity you're trying to insert does not have any fields."
        (Text
field:[Text]
_) -> Text
field
    entityFieldNames :: [Text]
entityFieldNames = (FieldDef -> Text) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map FieldDef -> Text
fieldDbToText (EntityDef -> [FieldDef]
getEntityFields EntityDef
entityDef')
    nameOfTable :: Text
nameOfTable = EntityNameDB -> Text
escapeE (EntityNameDB -> Text)
-> (EntityDef -> EntityNameDB) -> EntityDef -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntityDef -> EntityNameDB
getEntityDBName (EntityDef -> Text) -> EntityDef -> Text
forall a b. (a -> b) -> a -> b
$ EntityDef
entityDef'
    copyUnlessValues :: [PersistValue]
copyUnlessValues = ((Text, PersistValue) -> PersistValue)
-> [(Text, PersistValue)] -> [PersistValue]
forall a b. (a -> b) -> [a] -> [b]
map (Text, PersistValue) -> PersistValue
forall a b. (a, b) -> b
snd [(Text, PersistValue)]
fieldsToMaybeCopy
    recordValues :: [PersistValue]
recordValues = (record -> [PersistValue]) -> [record] -> [PersistValue]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((SomePersistField -> PersistValue)
-> [SomePersistField] -> [PersistValue]
forall a b. (a -> b) -> [a] -> [b]
map SomePersistField -> PersistValue
forall a. PersistField a => a -> PersistValue
toPersistValue ([SomePersistField] -> [PersistValue])
-> (record -> [SomePersistField]) -> record -> [PersistValue]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. record -> [SomePersistField]
forall record. PersistEntity record => record -> [SomePersistField]
toPersistFields) [record]
records
    recordPlaceholders :: Text
recordPlaceholders =
        [Text] -> Text
Util.commaSeparated
        ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (record -> Text) -> [record] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Text
Util.parenWrapped (Text -> Text) -> (record -> Text) -> record -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
Util.commaSeparated ([Text] -> Text) -> (record -> [Text]) -> record -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SomePersistField -> Text) -> [SomePersistField] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> SomePersistField -> Text
forall a b. a -> b -> a
const Text
"?") ([SomePersistField] -> [Text])
-> (record -> [SomePersistField]) -> record -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. record -> [SomePersistField]
forall record. PersistEntity record => record -> [SomePersistField]
toPersistFields)
        ([record] -> [Text]) -> [record] -> [Text]
forall a b. (a -> b) -> a -> b
$ [record]
records
    mkCondFieldSet :: Text -> PersistValue -> Text
mkCondFieldSet Text
n PersistValue
_ =
        [Text] -> Text
T.concat
            [ Text
n
            , Text
"=COALESCE("
            ,   Text
"NULLIF("
            ,     Text
"EXCLUDED."
            ,       Text
n
            ,         Text
","
            ,           Text
"?"
            ,         Text
")"
            ,       Text
","
            ,     Text
nameOfTable
            ,   Text
"."
            ,   Text
n
            ,Text
")"
            ]
    condFieldSets :: [Text]
condFieldSets = ((Text, PersistValue) -> Text) -> [(Text, PersistValue)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ((Text -> PersistValue -> Text) -> (Text, PersistValue) -> Text
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Text -> PersistValue -> Text
mkCondFieldSet) [(Text, PersistValue)]
fieldsToMaybeCopy
    fieldSets :: [Text]
fieldSets = (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (\Text
n -> [Text] -> Text
T.concat [Text
n, Text
"=EXCLUDED.", Text
n, Text
""]) [Text]
updateFieldNames
    upds :: [Text]
upds = (Update record -> Text) -> [Update record] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ((FieldNameDB -> Text) -> (Text -> Text) -> Update record -> Text
forall record.
PersistEntity record =>
(FieldNameDB -> Text) -> (Text -> Text) -> Update record -> Text
Util.mkUpdateText' (FieldNameDB -> Text
escapeF) (\Text
n -> [Text] -> Text
T.concat [Text
nameOfTable, Text
".", Text
n])) [Update record]
updates
    updsValues :: [PersistValue]
updsValues = (Update record -> PersistValue)
-> [Update record] -> [PersistValue]
forall a b. (a -> b) -> [a] -> [b]
map (\(Update EntityField record typ
_ typ
val PersistUpdate
_) -> typ -> PersistValue
forall a. PersistField a => a -> PersistValue
toPersistValue typ
val) [Update record]
updates
    (Text
wher, [PersistValue]
whereVals) =
        if [Filter record] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Filter record]
filters
        then (Text
"", [])
        else (Maybe FilterTablePrefix
-> SqlBackend -> [Filter record] -> (Text, [PersistValue])
forall val.
PersistEntity val =>
Maybe FilterTablePrefix
-> SqlBackend -> [Filter val] -> (Text, [PersistValue])
filterClauseWithVals (FilterTablePrefix -> Maybe FilterTablePrefix
forall a. a -> Maybe a
Just FilterTablePrefix
PrefixTableName) SqlBackend
conn [Filter record]
filters)
    updateText :: Text
updateText =
        case [Text]
fieldSets [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Text]
upds [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Text]
condFieldSets of
            [] ->
                -- This case is really annoying, and probably unlikely to be
                -- actually hit - someone would have had to call something like
                -- `upsertManyWhere [] [] []`, but that would have been caught
                -- by the prior case.
                -- Would be nice to have something like a `NonEmpty (These ...)`
                -- instead of multiple lists...
                [Text] -> Text
T.concat [Text
firstField, Text
"=", Text
nameOfTable, Text
".", Text
firstField]
            [Text]
xs ->
                [Text] -> Text
Util.commaSeparated [Text]
xs
    q :: Text
q = [Text] -> Text
T.concat
        [ Text
"INSERT INTO "
        , Text
nameOfTable
        , Text -> Text
Util.parenWrapped (Text -> Text) -> ([Text] -> Text) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
Util.commaSeparated ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text]
entityFieldNames
        , Text
" VALUES "
        , Text
recordPlaceholders
        , Text
" ON CONFLICT "
        , Text -> Text
Util.parenWrapped (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
Util.commaSeparated ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text]
conflictColumns
        , Text
" DO UPDATE SET "
        , Text
updateText
        , Text
wher
        ]

putManySql' :: [Text] -> [FieldDef] -> EntityDef -> Int -> Text
putManySql' :: [Text] -> [FieldDef] -> EntityDef -> Int -> Text
putManySql' [Text]
conflictColumns ((FieldDef -> Bool) -> [FieldDef] -> [FieldDef]
forall a. (a -> Bool) -> [a] -> [a]
filter FieldDef -> Bool
isFieldNotGenerated -> [FieldDef]
fields) EntityDef
ent Int
n = Text
q
  where
    fieldDbToText :: FieldDef -> Text
fieldDbToText = FieldNameDB -> Text
escapeF (FieldNameDB -> Text)
-> (FieldDef -> FieldNameDB) -> FieldDef -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldDef -> FieldNameDB
fieldDB
    mkAssignment :: Text -> Text
mkAssignment Text
f = [Text] -> Text
T.concat [Text
f, Text
"=EXCLUDED.", Text
f]

    table :: Text
table = EntityNameDB -> Text
escapeE (EntityNameDB -> Text)
-> (EntityDef -> EntityNameDB) -> EntityDef -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntityDef -> EntityNameDB
getEntityDBName (EntityDef -> Text) -> EntityDef -> Text
forall a b. (a -> b) -> a -> b
$ EntityDef
ent
    columns :: Text
columns = [Text] -> Text
Util.commaSeparated ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (FieldDef -> Text) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map FieldDef -> Text
fieldDbToText [FieldDef]
fields
    placeholders :: [Text]
placeholders = (FieldDef -> Text) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> FieldDef -> Text
forall a b. a -> b -> a
const Text
"?") [FieldDef]
fields
    updates :: [Text]
updates = (FieldDef -> Text) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Text
mkAssignment (Text -> Text) -> (FieldDef -> Text) -> FieldDef -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldDef -> Text
fieldDbToText) [FieldDef]
fields

    q :: Text
q = [Text] -> Text
T.concat
        [ Text
"INSERT INTO "
        , Text
table
        , Text -> Text
Util.parenWrapped Text
columns
        , Text
" VALUES "
        , [Text] -> Text
Util.commaSeparated ([Text] -> Text) -> ([Text] -> [Text]) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text -> [Text]
forall a. Int -> a -> [a]
replicate Int
n
            (Text -> [Text]) -> ([Text] -> Text) -> [Text] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
Util.parenWrapped (Text -> Text) -> ([Text] -> Text) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
Util.commaSeparated ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text]
placeholders
        , Text
" ON CONFLICT "
        , Text -> Text
Util.parenWrapped (Text -> Text) -> ([Text] -> Text) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
Util.commaSeparated ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text]
conflictColumns
        , Text
" DO UPDATE SET "
        , [Text] -> Text
Util.commaSeparated [Text]
updates
        ]


-- | Enable a Postgres extension. See https://www.postgresql.org/docs/current/static/contrib.html
-- for a list.
migrateEnableExtension :: Text -> Migration
migrateEnableExtension :: Text -> Migration
migrateEnableExtension Text
extName = WriterT [(Bool, Text)] (ReaderT SqlBackend IO) ((), [Text])
-> Migration
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (WriterT [(Bool, Text)] (ReaderT SqlBackend IO) ((), [Text])
 -> Migration)
-> WriterT [(Bool, Text)] (ReaderT SqlBackend IO) ((), [Text])
-> Migration
forall a b. (a -> b) -> a -> b
$ ReaderT SqlBackend IO (((), [Text]), [(Bool, Text)])
-> WriterT [(Bool, Text)] (ReaderT SqlBackend IO) ((), [Text])
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (ReaderT SqlBackend IO (((), [Text]), [(Bool, Text)])
 -> WriterT [(Bool, Text)] (ReaderT SqlBackend IO) ((), [Text]))
-> ReaderT SqlBackend IO (((), [Text]), [(Bool, Text)])
-> WriterT [(Bool, Text)] (ReaderT SqlBackend IO) ((), [Text])
forall a b. (a -> b) -> a -> b
$ do
  [Single Int]
res :: [Single Int] <-
    Text -> [PersistValue] -> ReaderT SqlBackend IO [Single Int]
forall a (m :: * -> *) backend.
(RawSql a, MonadIO m, BackendCompatible SqlBackend backend) =>
Text -> [PersistValue] -> ReaderT backend m [a]
rawSql Text
"SELECT COUNT(*) FROM pg_catalog.pg_extension WHERE extname = ?" [Text -> PersistValue
PersistText Text
extName]
  if [Single Int]
res [Single Int] -> [Single Int] -> Bool
forall a. Eq a => a -> a -> Bool
== [Int -> Single Int
forall a. a -> Single a
Single Int
0]
    then (((), [Text]), [(Bool, Text)])
-> ReaderT SqlBackend IO (((), [Text]), [(Bool, Text)])
forall (m :: * -> *) a. Monad m => a -> m a
return (((), []) , [(Bool
False, Text
"CREATe EXTENSION \"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
extName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\"")])
    else (((), [Text]), [(Bool, Text)])
-> ReaderT SqlBackend IO (((), [Text]), [(Bool, Text)])
forall (m :: * -> *) a. Monad m => a -> m a
return (((), []), [])

postgresMkColumns :: [EntityDef] -> EntityDef -> ([Column], [UniqueDef], [ForeignDef])
postgresMkColumns :: [EntityDef] -> EntityDef -> ([Column], [UniqueDef], [ForeignDef])
postgresMkColumns [EntityDef]
allDefs EntityDef
t =
    [EntityDef]
-> EntityDef
-> BackendSpecificOverrides
-> ([Column], [UniqueDef], [ForeignDef])
mkColumns [EntityDef]
allDefs EntityDef
t
    (BackendSpecificOverrides -> ([Column], [UniqueDef], [ForeignDef]))
-> BackendSpecificOverrides
-> ([Column], [UniqueDef], [ForeignDef])
forall a b. (a -> b) -> a -> b
$ (EntityNameDB -> FieldNameDB -> ConstraintNameDB)
-> BackendSpecificOverrides -> BackendSpecificOverrides
setBackendSpecificForeignKeyName EntityNameDB -> FieldNameDB -> ConstraintNameDB
refName BackendSpecificOverrides
emptyBackendSpecificOverrides

-- | Wrapper for persistent SqlBackends that carry the corresponding
-- `Postgresql.Connection`.
--
-- @since 2.13.1.0
data RawPostgresql backend = RawPostgresql
    { RawPostgresql backend -> backend
persistentBackend :: backend
    -- ^ The persistent backend
    --
    -- @since 2.13.1.0
    , RawPostgresql backend -> Connection
rawPostgresqlConnection :: PG.Connection
    -- ^ The underlying `PG.Connection`
    --
    -- @since 2.13.1.0
    }

instance BackendCompatible (RawPostgresql b) (RawPostgresql b) where
    projectBackend :: RawPostgresql b -> RawPostgresql b
projectBackend = RawPostgresql b -> RawPostgresql b
forall a. a -> a
id

instance BackendCompatible b (RawPostgresql b) where
    projectBackend :: RawPostgresql b -> b
projectBackend = RawPostgresql b -> b
forall b. RawPostgresql b -> b
persistentBackend

withRawConnection
    :: (PG.Connection -> SqlBackend)
    -> PG.Connection
    -> RawPostgresql SqlBackend
withRawConnection :: (Connection -> SqlBackend)
-> Connection -> RawPostgresql SqlBackend
withRawConnection Connection -> SqlBackend
f Connection
conn = RawPostgresql :: forall backend. backend -> Connection -> RawPostgresql backend
RawPostgresql
    { persistentBackend :: SqlBackend
persistentBackend = Connection -> SqlBackend
f Connection
conn
    , rawPostgresqlConnection :: Connection
rawPostgresqlConnection = Connection
conn
    }

-- | Create a PostgreSQL connection pool which also exposes the
-- raw connection. The raw counterpart to 'createPostgresqlPool'.
--
-- @since 2.13.1.0
createRawPostgresqlPool :: (MonadUnliftIO m, MonadLoggerIO m)
                     => ConnectionString
                     -- ^ Connection string to the database.
                     -> Int
                     -- ^ Number of connections to be kept open
                     -- in the pool.
                     -> m (Pool (RawPostgresql SqlBackend))
createRawPostgresqlPool :: ConnectionString -> Int -> m (Pool (RawPostgresql SqlBackend))
createRawPostgresqlPool = (Connection -> IO ())
-> ConnectionString -> Int -> m (Pool (RawPostgresql SqlBackend))
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
(Connection -> IO ())
-> ConnectionString -> Int -> m (Pool (RawPostgresql SqlBackend))
createRawPostgresqlPoolModified (IO () -> Connection -> IO ()
forall a b. a -> b -> a
const (IO () -> Connection -> IO ()) -> IO () -> Connection -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())

-- | The raw counterpart to 'createPostgresqlPoolModified'.
--
-- @since 2.13.1.0
createRawPostgresqlPoolModified
    :: (MonadUnliftIO m, MonadLoggerIO m)
    => (PG.Connection -> IO ()) -- ^ Action to perform after connection is created.
    -> ConnectionString -- ^ Connection string to the database.
    -> Int -- ^ Number of connections to be kept open in the pool.
    -> m (Pool (RawPostgresql SqlBackend))
createRawPostgresqlPoolModified :: (Connection -> IO ())
-> ConnectionString -> Int -> m (Pool (RawPostgresql SqlBackend))
createRawPostgresqlPoolModified = (Connection -> IO (Maybe Double))
-> (Connection -> IO ())
-> ConnectionString
-> Int
-> m (Pool (RawPostgresql SqlBackend))
forall (m :: * -> *).
(MonadUnliftIO m, MonadLoggerIO m) =>
(Connection -> IO (Maybe Double))
-> (Connection -> IO ())
-> ConnectionString
-> Int
-> m (Pool (RawPostgresql SqlBackend))
createRawPostgresqlPoolModifiedWithVersion Connection -> IO (Maybe Double)
getServerVersion

-- | The raw counterpart to 'createPostgresqlPoolModifiedWithVersion'.
--
-- @since 2.13.1.0
createRawPostgresqlPoolModifiedWithVersion
    :: (MonadUnliftIO m, MonadLoggerIO m)
    => (PG.Connection -> IO (Maybe Double)) -- ^ Action to perform to get the server version.
    -> (PG.Connection -> IO ()) -- ^ Action to perform after connection is created.
    -> ConnectionString -- ^ Connection string to the database.
    -> Int -- ^ Number of connections to be kept open in the pool.
    -> m (Pool (RawPostgresql SqlBackend))
createRawPostgresqlPoolModifiedWithVersion :: (Connection -> IO (Maybe Double))
-> (Connection -> IO ())
-> ConnectionString
-> Int
-> m (Pool (RawPostgresql SqlBackend))
createRawPostgresqlPoolModifiedWithVersion Connection -> IO (Maybe Double)
getVerDouble Connection -> IO ()
modConn ConnectionString
ci = do
  let getVer :: Connection -> IO (NonEmpty Word)
getVer = (Connection -> IO (Maybe Double))
-> Connection -> IO (NonEmpty Word)
oldGetVersionToNew Connection -> IO (Maybe Double)
getVerDouble
  (LogFunc -> IO (RawPostgresql SqlBackend))
-> Int -> m (Pool (RawPostgresql SqlBackend))
forall backend (m :: * -> *).
(MonadLoggerIO m, MonadUnliftIO m,
 BackendCompatible SqlBackend backend) =>
(LogFunc -> IO backend) -> Int -> m (Pool backend)
createSqlPool ((LogFunc -> IO (RawPostgresql SqlBackend))
 -> Int -> m (Pool (RawPostgresql SqlBackend)))
-> (LogFunc -> IO (RawPostgresql SqlBackend))
-> Int
-> m (Pool (RawPostgresql SqlBackend))
forall a b. (a -> b) -> a -> b
$ (Connection -> IO ())
-> (Connection -> IO (NonEmpty Word))
-> ((Connection -> SqlBackend)
    -> Connection -> RawPostgresql SqlBackend)
-> ConnectionString
-> LogFunc
-> IO (RawPostgresql SqlBackend)
forall backend.
(Connection -> IO ())
-> (Connection -> IO (NonEmpty Word))
-> ((Connection -> SqlBackend) -> Connection -> backend)
-> ConnectionString
-> LogFunc
-> IO backend
open' Connection -> IO ()
modConn Connection -> IO (NonEmpty Word)
getVer (Connection -> SqlBackend)
-> Connection -> RawPostgresql SqlBackend
withRawConnection ConnectionString
ci

-- | The raw counterpart to 'createPostgresqlPoolWithConf'.
--
-- @since 2.13.1.0
createRawPostgresqlPoolWithConf
    :: (MonadUnliftIO m, MonadLoggerIO m)
    => PostgresConf -- ^ Configuration for connecting to Postgres
    -> PostgresConfHooks -- ^ Record of callback functions
    -> m (Pool (RawPostgresql SqlBackend))
createRawPostgresqlPoolWithConf :: PostgresConf
-> PostgresConfHooks -> m (Pool (RawPostgresql SqlBackend))
createRawPostgresqlPoolWithConf PostgresConf
conf PostgresConfHooks
hooks = do
  let getVer :: Connection -> IO (NonEmpty Word)
getVer = PostgresConfHooks -> Connection -> IO (NonEmpty Word)
pgConfHooksGetServerVersion PostgresConfHooks
hooks
      modConn :: Connection -> IO ()
modConn = PostgresConfHooks -> Connection -> IO ()
pgConfHooksAfterCreate PostgresConfHooks
hooks
  (LogFunc -> IO (RawPostgresql SqlBackend))
-> ConnectionPoolConfig -> m (Pool (RawPostgresql SqlBackend))
forall (m :: * -> *) backend.
(MonadLoggerIO m, MonadUnliftIO m,
 BackendCompatible SqlBackend backend) =>
(LogFunc -> IO backend) -> ConnectionPoolConfig -> m (Pool backend)
createSqlPoolWithConfig ((Connection -> IO ())
-> (Connection -> IO (NonEmpty Word))
-> ((Connection -> SqlBackend)
    -> Connection -> RawPostgresql SqlBackend)
-> ConnectionString
-> LogFunc
-> IO (RawPostgresql SqlBackend)
forall backend.
(Connection -> IO ())
-> (Connection -> IO (NonEmpty Word))
-> ((Connection -> SqlBackend) -> Connection -> backend)
-> ConnectionString
-> LogFunc
-> IO backend
open' Connection -> IO ()
modConn Connection -> IO (NonEmpty Word)
getVer (Connection -> SqlBackend)
-> Connection -> RawPostgresql SqlBackend
withRawConnection (PostgresConf -> ConnectionString
pgConnStr PostgresConf
conf)) (PostgresConf -> ConnectionPoolConfig
postgresConfToConnectionPoolConfig PostgresConf
conf)

#if MIN_VERSION_base(4,12,0)
instance (PersistCore b) => PersistCore (RawPostgresql b) where
  newtype BackendKey (RawPostgresql b) = RawPostgresqlKey { BackendKey (RawPostgresql b)
-> BackendKey (Compatible b (RawPostgresql b))
unRawPostgresqlKey :: BackendKey (Compatible b (RawPostgresql b)) }

makeCompatibleKeyInstances [t| forall b. Compatible b (RawPostgresql b) |]
#else
instance (PersistCore b) => PersistCore (RawPostgresql b) where
  newtype BackendKey (RawPostgresql b) = RawPostgresqlKey { unRawPostgresqlKey :: BackendKey (RawPostgresql b) }

deriving instance (Show (BackendKey b)) => Show (BackendKey (RawPostgresql b))
deriving instance (Read (BackendKey b)) => Read (BackendKey (RawPostgresql b))
deriving instance (Eq (BackendKey b)) => Eq (BackendKey (RawPostgresql b))
deriving instance (Ord (BackendKey b)) => Ord (BackendKey (RawPostgresql b))
deriving instance (Num (BackendKey b)) => Num (BackendKey (RawPostgresql b))
deriving instance (Integral (BackendKey b)) => Integral (BackendKey (RawPostgresql b))
deriving instance (PersistField (BackendKey b)) => PersistField (BackendKey (RawPostgresql b))
deriving instance (PersistFieldSql (BackendKey b)) => PersistFieldSql (BackendKey (RawPostgresql b))
deriving instance (Real (BackendKey b)) => Real (BackendKey (RawPostgresql b))
deriving instance (Enum (BackendKey b)) => Enum (BackendKey (RawPostgresql b))
deriving instance (Bounded (BackendKey b)) => Bounded (BackendKey (RawPostgresql b))
deriving instance (ToJSON (BackendKey b)) => ToJSON (BackendKey (RawPostgresql b))
deriving instance (FromJSON (BackendKey b)) => FromJSON (BackendKey (RawPostgresql b))
#endif


#if MIN_VERSION_base(4,12,0)
$(pure [])

makeCompatibleInstances [t| forall b. Compatible b (RawPostgresql b) |]
#else
instance HasPersistBackend b => HasPersistBackend (RawPostgresql b) where
    type BaseBackend (RawPostgresql b) = BaseBackend b
    persistBackend = persistBackend . persistentBackend

instance (PersistStoreRead b) => PersistStoreRead (RawPostgresql b) where
    get = withReaderT persistentBackend . get
    getMany = withReaderT persistentBackend . getMany

instance (PersistQueryRead b) => PersistQueryRead (RawPostgresql b) where
    selectSourceRes filts opts = withReaderT persistentBackend $ selectSourceRes filts opts
    selectFirst filts opts = withReaderT persistentBackend $ selectFirst filts opts
    selectKeysRes filts opts = withReaderT persistentBackend $ selectKeysRes filts opts
    count = withReaderT persistentBackend . count
    exists = withReaderT persistentBackend . exists

instance (PersistQueryWrite b) => PersistQueryWrite (RawPostgresql b) where
    updateWhere filts updates = withReaderT persistentBackend $ updateWhere filts updates
    deleteWhere = withReaderT persistentBackend . deleteWhere

instance (PersistUniqueRead b) => PersistUniqueRead (RawPostgresql b) where
    getBy = withReaderT persistentBackend . getBy

instance (PersistStoreWrite b) => PersistStoreWrite (RawPostgresql b) where
    insert = withReaderT persistentBackend . insert
    insert_ = withReaderT persistentBackend . insert_
    insertMany = withReaderT persistentBackend . insertMany
    insertMany_ = withReaderT persistentBackend . insertMany_
    insertEntityMany = withReaderT persistentBackend . insertEntityMany
    insertKey k = withReaderT persistentBackend . insertKey k
    repsert k = withReaderT persistentBackend . repsert k
    repsertMany = withReaderT persistentBackend . repsertMany
    replace k = withReaderT persistentBackend . replace k
    delete = withReaderT persistentBackend . delete
    update k = withReaderT persistentBackend . update k
    updateGet k = withReaderT persistentBackend . updateGet k

instance (PersistUniqueWrite b) => PersistUniqueWrite (RawPostgresql b) where
    deleteBy = withReaderT persistentBackend . deleteBy
    insertUnique = withReaderT persistentBackend . insertUnique
    upsert rec = withReaderT persistentBackend . upsert rec
    upsertBy uniq rec = withReaderT persistentBackend . upsertBy uniq rec
    putMany = withReaderT persistentBackend . putMany
#endif