{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}

-- | A postgresql backend for persistent.
module Database.Persist.Postgresql
    ( withPostgresqlPool
    , withPostgresqlPoolWithVersion
    , withPostgresqlConn
    , withPostgresqlConnWithVersion
    , createPostgresqlPool
    , createPostgresqlPoolModified
    , createPostgresqlPoolModifiedWithVersion
    , module Database.Persist.Sql
    , ConnectionString
    , PostgresConf (..)
    , openSimpleConn
    , openSimpleConnWithVersion
    , tableName
    , fieldName
    , mockMigration
    , migrateEnableExtension
    ) where

import qualified Database.PostgreSQL.LibPQ as LibPQ

import qualified Database.PostgreSQL.Simple as PG
import qualified Database.PostgreSQL.Simple.Internal as PG
import qualified Database.PostgreSQL.Simple.FromField as PGFF
import qualified Database.PostgreSQL.Simple.ToField as PGTF
import qualified Database.PostgreSQL.Simple.Transaction as PG
import qualified Database.PostgreSQL.Simple.Types as PG
import qualified Database.PostgreSQL.Simple.TypeInfo.Static as PS
import Database.PostgreSQL.Simple.Ok (Ok (..))

import Control.Arrow
import Control.Exception (Exception, throw, throwIO)
import Control.Monad (forM)
import Control.Monad.IO.Unlift (MonadIO (..), MonadUnliftIO)
import Control.Monad.Logger (MonadLogger, runNoLoggingT)
import Control.Monad.Trans.Reader (runReaderT)
import Control.Monad.Trans.Writer (WriterT(..), runWriterT)

import qualified Blaze.ByteString.Builder.Char8 as BBB
import Data.Acquire (Acquire, mkAcquire, with)
import Data.Aeson
import Data.Aeson.Types (modifyFailure)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as B8
import Data.Conduit
import qualified Data.Conduit.List as CL
import Data.Data
import Data.Either (partitionEithers)
import Data.Fixed (Pico)
import Data.Function (on)
import Data.Int (Int64)
import qualified Data.IntMap as I
import Data.IORef
import Data.List (find, sort, groupBy)
import Data.List.NonEmpty (NonEmpty)
import qualified Data.List.NonEmpty as NEL
import qualified Data.Map as Map
import Data.Maybe
import Data.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 Data.Time (utc, localTimeToUTC)
import Data.Typeable (Typeable)
import System.Environment (getEnvironment)

import Database.Persist.Sql
import qualified Database.Persist.Sql.Util as Util

-- | 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 deriving Data.Typeable.Typeable

instance Show PostgresServerVersionError where
    show :: PostgresServerVersionError -> String
show (PostgresServerVersionError uniqueMsg :: String
uniqueMsg) =
      "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 :: (MonadLogger 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 ci :: ConnectionString
ci = (Connection -> IO (Maybe Double))
-> ConnectionString -> Int -> (Pool SqlBackend -> m a) -> m a
forall (m :: * -> *) a.
(MonadUnliftIO m, MonadLogger 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, MonadLogger 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 getVer :: Connection -> IO (Maybe Double)
getVer ci :: ConnectionString
ci = (LogFunc -> IO SqlBackend)
-> Int -> (Pool SqlBackend -> m a) -> m a
forall (m :: * -> *) backend a.
(MonadLogger 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 (Maybe Double))
-> ConnectionString
-> LogFunc
-> IO SqlBackend
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 (Maybe Double)
getVer ConnectionString
ci

-- | 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, MonadLogger 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, MonadLogger 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, MonadLogger 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, MonadLogger 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, MonadLogger 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 getVer :: Connection -> IO (Maybe Double)
getVer modConn :: Connection -> IO ()
modConn ci :: ConnectionString
ci =
  (LogFunc -> IO SqlBackend) -> Int -> m (Pool SqlBackend)
forall (m :: * -> *) backend.
(MonadLogger 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 (Maybe Double))
-> ConnectionString
-> LogFunc
-> IO SqlBackend
open' Connection -> IO ()
modConn Connection -> IO (Maybe Double)
getVer ConnectionString
ci

-- | 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, MonadLogger 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, MonadLogger 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, MonadLogger m)
                              => (PG.Connection -> IO (Maybe Double))
                              -> ConnectionString
                              -> (SqlBackend -> m a)
                              -> m a
withPostgresqlConnWithVersion :: (Connection -> IO (Maybe Double))
-> ConnectionString -> (SqlBackend -> m a) -> m a
withPostgresqlConnWithVersion getVer :: Connection -> IO (Maybe Double)
getVer = (LogFunc -> IO SqlBackend) -> (SqlBackend -> m a) -> m a
forall (m :: * -> *) backend a.
(MonadUnliftIO m, MonadLogger 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 (Maybe Double))
-> ConnectionString
-> LogFunc
-> IO SqlBackend
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 (Maybe Double)
getVer

open'
    :: (PG.Connection -> IO ())
    -> (PG.Connection -> IO (Maybe Double))
    -> ConnectionString -> LogFunc -> IO SqlBackend
open' :: (Connection -> IO ())
-> (Connection -> IO (Maybe Double))
-> ConnectionString
-> LogFunc
-> IO SqlBackend
open' modConn :: Connection -> IO ()
modConn getVer :: Connection -> IO (Maybe Double)
getVer cstr :: ConnectionString
cstr logFunc :: LogFunc
logFunc = do
    Connection
conn <- ConnectionString -> IO Connection
PG.connectPostgreSQL ConnectionString
cstr
    Connection -> IO ()
modConn Connection
conn
    Maybe Double
ver <- Connection -> IO (Maybe Double)
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 -> IO (IORef (Map Text Statement)))
-> Map Text Statement -> IO (IORef (Map Text Statement))
forall a b. (a -> b) -> a -> b
$ Map Text Statement
forall k a. Map k a
Map.empty
    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
-> Maybe Double
-> IORef (Map Text Statement)
-> Connection
-> SqlBackend
createBackend LogFunc
logFunc Maybe Double
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 conn :: Connection
conn = do
  [PG.Only version :: Text
version] <- Connection -> Query -> IO [Only Text]
forall r. FromRow r => Connection -> Query -> IO [r]
PG.query_ Connection
conn "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 (a :: Double
a,_) -> 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 err :: 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

-- | 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 -> Double -> Maybe a
upsertFunction :: a -> Double -> Maybe a
upsertFunction f :: a
f version :: Double
version = if (Double
version Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= 9.5)
                         then a -> Maybe a
forall a. a -> Maybe a
Just a
f
                         else Maybe a
forall a. Maybe a
Nothing


-- | 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 getVer :: Connection -> IO (Maybe Double)
getVer logFunc :: LogFunc
logFunc conn :: 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 -> IO (IORef (Map Text Statement)))
-> Map Text Statement -> IO (IORef (Map Text Statement))
forall a b. (a -> b) -> a -> b
$ Map Text Statement
forall k a. Map k a
Map.empty
    Maybe Double
serverVersion <- Connection -> IO (Maybe Double)
getVer 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
-> Maybe Double
-> IORef (Map Text Statement)
-> Connection
-> SqlBackend
createBackend LogFunc
logFunc Maybe Double
serverVersion IORef (Map Text Statement)
smap Connection
conn

-- | Create the backend given a logging function, server version, mutable statement cell,
-- and connection.
createBackend :: LogFunc -> Maybe Double
              -> IORef (Map.Map Text Statement) -> PG.Connection -> SqlBackend
createBackend :: LogFunc
-> Maybe Double
-> IORef (Map Text Statement)
-> Connection
-> SqlBackend
createBackend logFunc :: LogFunc
logFunc serverVersion :: Maybe Double
serverVersion smap :: IORef (Map Text Statement)
smap conn :: Connection
conn = do
    SqlBackend :: (Text -> IO Statement)
-> (EntityDef -> [PersistValue] -> InsertSqlResult)
-> Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
-> Maybe (EntityDef -> NonEmpty UniqueDef -> Text -> Text)
-> Maybe (EntityDef -> Int -> Text)
-> 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 ())
-> (DBName -> Text)
-> Text
-> Text
-> ((Int, Int) -> Bool -> Text -> Text)
-> LogFunc
-> Maybe Int
-> Maybe (EntityDef -> Int -> Text)
-> SqlBackend
SqlBackend
        { 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'
        , connInsertManySql :: Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
connInsertManySql = (EntityDef -> [[PersistValue]] -> InsertSqlResult)
-> Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
forall a. a -> Maybe a
Just EntityDef -> [[PersistValue]] -> InsertSqlResult
insertManySql'
        , connUpsertSql :: Maybe (EntityDef -> NonEmpty UniqueDef -> Text -> Text)
connUpsertSql  = Maybe Double
serverVersion Maybe Double
-> (Double
    -> Maybe (EntityDef -> NonEmpty UniqueDef -> Text -> Text))
-> Maybe (EntityDef -> NonEmpty UniqueDef -> Text -> Text)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (EntityDef -> NonEmpty UniqueDef -> Text -> Text)
-> Double
-> Maybe (EntityDef -> NonEmpty UniqueDef -> Text -> Text)
forall a. a -> Double -> Maybe a
upsertFunction EntityDef -> NonEmpty UniqueDef -> Text -> Text
upsertSql'
        , connPutManySql :: Maybe (EntityDef -> Int -> Text)
connPutManySql = Maybe Double
serverVersion Maybe Double
-> (Double -> Maybe (EntityDef -> Int -> Text))
-> Maybe (EntityDef -> Int -> Text)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (EntityDef -> Int -> Text)
-> Double -> Maybe (EntityDef -> Int -> Text)
forall a. a -> Double -> Maybe a
upsertFunction EntityDef -> Int -> Text
putManySql
        , 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      = \_ mIsolation :: Maybe IsolationLevel
mIsolation -> case Maybe IsolationLevel
mIsolation of
              Nothing -> Connection -> IO ()
PG.begin Connection
conn
              Just iso :: IsolationLevel
iso -> IsolationLevel -> Connection -> IO ()
PG.beginLevel (case IsolationLevel
iso of
                  ReadUncommitted -> IsolationLevel
PG.ReadCommitted -- PG Upgrades uncommitted reads to committed anyways
                  ReadCommitted -> IsolationLevel
PG.ReadCommitted
                  RepeatableRead -> IsolationLevel
PG.RepeatableRead
                  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
        , connEscapeName :: DBName -> Text
connEscapeName = DBName -> Text
escape
        , connNoLimit :: Text
connNoLimit    = "LIMIT ALL"
        , connRDBMS :: Text
connRDBMS      = "postgresql"
        , connLimitOffset :: (Int, Int) -> Bool -> Text -> Text
connLimitOffset = Text -> (Int, Int) -> Bool -> Text -> Text
decorateSQLWithLimitOffset "LIMIT ALL"
        , connLogFunc :: LogFunc
connLogFunc = LogFunc
logFunc
        , connMaxParams :: Maybe Int
connMaxParams = Maybe Int
forall a. Maybe a
Nothing
        , connRepsertManySql :: Maybe (EntityDef -> Int -> Text)
connRepsertManySql = Maybe Double
serverVersion Maybe Double
-> (Double -> Maybe (EntityDef -> Int -> Text))
-> Maybe (EntityDef -> Int -> Text)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (EntityDef -> Int -> Text)
-> Double -> Maybe (EntityDef -> Int -> Text)
forall a. a -> Double -> Maybe a
upsertFunction EntityDef -> Int -> Text
repsertManySql
        }

prepare' :: PG.Connection -> Text -> IO Statement
prepare' :: Connection -> Text -> IO Statement
prepare' conn :: Connection
conn sql :: 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' ent :: EntityDef
ent vals :: [PersistValue]
vals =
  let sql :: Text
sql = [Text] -> Text
T.concat
                [ "INSERT INTO "
                , DBName -> Text
escape (DBName -> Text) -> DBName -> Text
forall a b. (a -> b) -> a -> b
$ EntityDef -> DBName
entityDB EntityDef
ent
                , if [FieldDef] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (EntityDef -> [FieldDef]
entityFields EntityDef
ent)
                    then " DEFAULT VALUES"
                    else [Text] -> Text
T.concat
                        [ "("
                        , Text -> [Text] -> Text
T.intercalate "," ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (FieldDef -> Text) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (DBName -> Text
escape (DBName -> Text) -> (FieldDef -> DBName) -> FieldDef -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldDef -> DBName
fieldDB) ([FieldDef] -> [Text]) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> a -> b
$ EntityDef -> [FieldDef]
entityFields EntityDef
ent
                        , ") VALUES("
                        , Text -> [Text] -> Text
T.intercalate "," ((FieldDef -> Text) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> FieldDef -> Text
forall a b. a -> b -> a
const "?") ([FieldDef] -> [Text]) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> a -> b
$ EntityDef -> [FieldDef]
entityFields EntityDef
ent)
                        , ")"
                        ]
                ]
  in case EntityDef -> Maybe CompositeDef
entityPrimary EntityDef
ent of
       Just _pdef :: CompositeDef
_pdef -> Text -> [PersistValue] -> InsertSqlResult
ISRManyKeys Text
sql [PersistValue]
vals
       Nothing -> Text -> InsertSqlResult
ISRSingle (Text
sql Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> " RETURNING " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> DBName -> Text
escape (FieldDef -> DBName
fieldDB (EntityDef -> FieldDef
entityId EntityDef
ent)))


upsertSql' :: EntityDef -> NonEmpty UniqueDef -> Text -> Text
upsertSql' :: EntityDef -> NonEmpty UniqueDef -> Text -> Text
upsertSql' ent :: EntityDef
ent uniqs :: NonEmpty UniqueDef
uniqs updateVal :: Text
updateVal = [Text] -> Text
T.concat
                           [ "INSERT INTO "
                           , DBName -> Text
escape (EntityDef -> DBName
entityDB EntityDef
ent)
                           , "("
                           , Text -> [Text] -> Text
T.intercalate "," ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (FieldDef -> Text) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (DBName -> Text
escape (DBName -> Text) -> (FieldDef -> DBName) -> FieldDef -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldDef -> DBName
fieldDB) ([FieldDef] -> [Text]) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> a -> b
$ EntityDef -> [FieldDef]
entityFields EntityDef
ent
                           , ") VALUES ("
                           , Text -> [Text] -> Text
T.intercalate "," ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (FieldDef -> Text) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> FieldDef -> Text
forall a b. a -> b -> a
const "?") (EntityDef -> [FieldDef]
entityFields EntityDef
ent)
                           , ") ON CONFLICT ("
                           , Text -> [Text] -> Text
T.intercalate "," ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [[Text]] -> [Text]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Text]] -> [Text]) -> [[Text]] -> [Text]
forall a b. (a -> b) -> a -> b
$ (UniqueDef -> [Text]) -> [UniqueDef] -> [[Text]]
forall a b. (a -> b) -> [a] -> [b]
map (\x :: UniqueDef
x -> (DBName -> Text) -> [DBName] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map DBName -> Text
escape (((HaskellName, DBName) -> DBName)
-> [(HaskellName, DBName)] -> [DBName]
forall a b. (a -> b) -> [a] -> [b]
map (HaskellName, DBName) -> DBName
forall a b. (a, b) -> b
snd ([(HaskellName, DBName)] -> [DBName])
-> [(HaskellName, DBName)] -> [DBName]
forall a b. (a -> b) -> a -> b
$ UniqueDef -> [(HaskellName, DBName)]
uniqueFields UniqueDef
x)) (EntityDef -> [UniqueDef]
entityUniques EntityDef
ent)
                           , ") DO UPDATE SET "
                           , Text
updateVal
                           , " WHERE "
                           , Text
wher
                           , " RETURNING ??"
                           ]
    where
      wher :: Text
wher = Text -> [Text] -> Text
T.intercalate " AND " ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (UniqueDef -> Text) -> [UniqueDef] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map UniqueDef -> Text
singleCondition ([UniqueDef] -> [Text]) -> [UniqueDef] -> [Text]
forall a b. (a -> b) -> a -> b
$ NonEmpty UniqueDef -> [UniqueDef]
forall a. NonEmpty a -> [a]
NEL.toList NonEmpty UniqueDef
uniqs

      singleCondition :: UniqueDef -> Text
      singleCondition :: UniqueDef -> Text
singleCondition udef :: UniqueDef
udef = Text -> [Text] -> Text
T.intercalate " AND " ((DBName -> Text) -> [DBName] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map DBName -> Text
singleClause ([DBName] -> [Text]) -> [DBName] -> [Text]
forall a b. (a -> b) -> a -> b
$ ((HaskellName, DBName) -> DBName)
-> [(HaskellName, DBName)] -> [DBName]
forall a b. (a -> b) -> [a] -> [b]
map (HaskellName, DBName) -> DBName
forall a b. (a, b) -> b
snd (UniqueDef -> [(HaskellName, DBName)]
uniqueFields UniqueDef
udef))

      singleClause :: DBName -> Text
      singleClause :: DBName -> Text
singleClause field :: DBName
field = DBName -> Text
escape (EntityDef -> DBName
entityDB EntityDef
ent) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> "." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (DBName -> Text
escape DBName
field) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> " =?"

-- | SQL for inserting multiple rows at once and returning their primary keys.
insertManySql' :: EntityDef -> [[PersistValue]] -> InsertSqlResult
insertManySql' :: EntityDef -> [[PersistValue]] -> InsertSqlResult
insertManySql' ent :: EntityDef
ent valss :: [[PersistValue]]
valss =
  let sql :: Text
sql = [Text] -> Text
T.concat
                [ "INSERT INTO "
                , DBName -> Text
escape (EntityDef -> DBName
entityDB EntityDef
ent)
                , "("
                , Text -> [Text] -> Text
T.intercalate "," ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (FieldDef -> Text) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (DBName -> Text
escape (DBName -> Text) -> (FieldDef -> DBName) -> FieldDef -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldDef -> DBName
fieldDB) ([FieldDef] -> [Text]) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> a -> b
$ EntityDef -> [FieldDef]
entityFields EntityDef
ent
                , ") VALUES ("
                , Text -> [Text] -> Text
T.intercalate "),(" ([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) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (FieldDef -> Text) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> FieldDef -> Text
forall a b. a -> b -> a
const "?") (EntityDef -> [FieldDef]
entityFields EntityDef
ent)
                , ") RETURNING "
                , [Text] -> Text
Util.commaSeparated ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (DBName -> Text) -> EntityDef -> [Text]
Util.dbIdColumnsEsc DBName -> Text
escape EntityDef
ent
                ]
  in Text -> InsertSqlResult
ISRSingle Text
sql

execute' :: PG.Connection -> PG.Query -> [PersistValue] -> IO Int64
execute' :: Connection -> Query -> [PersistValue] -> IO Int64
execute' conn :: Connection
conn query :: Query
query vals :: [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' conn :: Connection
conn query :: Query
query vals :: [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
      (rt :: Result
rt, rr :: IORef Row
rr, rc :: Row
rc, ids :: [(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
$ \rawconn :: Connection
rawconn -> do
            -- Execute query
            Maybe Result
mret <- Connection -> ConnectionString -> IO (Maybe Result)
LibPQ.exec Connection
rawconn ConnectionString
rawquery
            case Maybe Result
mret of
              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
                         Nothing -> "Postgresql.withStmt': unknown error"
                         Just e :: ConnectionString
e  -> "Postgresql.withStmt': " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ConnectionString -> String
B8.unpack ConnectionString
e
              Just ret :: Result
ret -> do
                -- Check result status
                ExecStatus
status <- Result -> IO ExecStatus
LibPQ.resultStatus Result
ret
                case ExecStatus
status of
                  LibPQ.TuplesOk -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
                  _ -> ConnectionString -> Result -> ExecStatus -> IO ()
forall a. ConnectionString -> Result -> ExecStatus -> IO a
PG.throwResultError "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 [0..Column
colsColumn -> Column -> Column
forall a. Num a => a -> a -> a
-1] ((Column -> IO (Column, Oid)) -> IO [(Column, Oid)])
-> (Column -> IO (Column, Oid)) -> IO [(Column, Oid)]
forall a b. (a -> b) -> a -> b
$ \col :: 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 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 (\(col :: Column
col, oid :: Oid
oid) -> Connection -> Oid -> Getter PersistValue
getGetter Connection
conn 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 (ret :: Result
ret, _, _, _) = Result -> IO ()
LibPQ.unsafeFreeResult Result
ret

    pull :: (Result, IORef Row, Row,
 [Maybe ConnectionString -> Conversion PersistValue])
-> ConduitM () [PersistValue] m ()
pull x :: (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
            Nothing -> () -> ConduitM () [PersistValue] m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
            Just z :: [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 (ret :: Result
ret, rowRef :: IORef Row
rowRef, rowCount :: Row
rowCount, getters :: [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 (\r :: Row
r -> (Row
rRow -> Row -> Row
forall a. Num a => a -> a -> a
+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 [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
$ \(getter :: Maybe ConnectionString -> Conversion PersistValue
getter, col :: 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
                                  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 bs :: 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
forall a b. a -> b -> b
`seq` case Ok PersistValue
ok of
                                                        Errors (exc :: SomeException
exc:_) -> SomeException -> IO PersistValue
forall a e. Exception e => e -> a
throw SomeException
exc
                                                        Errors [] -> String -> IO PersistValue
forall a. HasCallStack => String -> a
error "Got an Errors, but no exceptions"
                                                        Ok v :: PersistValue
v  -> PersistValue -> IO PersistValue
forall (m :: * -> *) a. Monad m => a -> m a
return PersistValue
v

-- | Avoid orphan instances.
newtype P = P PersistValue


instance PGTF.ToField P where
    toField :: P -> Action
toField (P (PersistText t :: Text
t))        = Text -> Action
forall a. ToField a => a -> Action
PGTF.toField Text
t
    toField (P (PersistByteString bs :: ConnectionString
bs)) = Binary ConnectionString -> Action
forall a. ToField a => a -> Action
PGTF.toField (ConnectionString -> Binary ConnectionString
forall a. a -> Binary a
PG.Binary ConnectionString
bs)
    toField (P (PersistInt64 i :: Int64
i))       = Int64 -> Action
forall a. ToField a => a -> Action
PGTF.toField Int64
i
    toField (P (PersistDouble d :: Double
d))      = Double -> Action
forall a. ToField a => a -> Action
PGTF.toField Double
d
    toField (P (PersistRational r :: Rational
r))    = Builder -> Action
PGTF.Plain (Builder -> Action) -> Builder -> Action
forall a b. (a -> b) -> a -> b
$
                                         String -> Builder
BBB.fromString (String -> Builder) -> String -> Builder
forall a b. (a -> b) -> a -> b
$
                                         Pico -> String
forall a. Show a => a -> String
show (Rational -> Pico
forall a. Fractional a => Rational -> a
fromRational Rational
r :: Pico) --  FIXME: Too Ambigous, can not select precision without information about field
    toField (P (PersistBool b :: Bool
b))        = Bool -> Action
forall a. ToField a => a -> Action
PGTF.toField Bool
b
    toField (P (PersistDay d :: Day
d))         = Day -> Action
forall a. ToField a => a -> Action
PGTF.toField Day
d
    toField (P (PersistTimeOfDay t :: TimeOfDay
t))   = TimeOfDay -> Action
forall a. ToField a => a -> Action
PGTF.toField TimeOfDay
t
    toField (P (PersistUTCTime t :: UTCTime
t))     = UTCTime -> Action
forall a. ToField a => a -> Action
PGTF.toField UTCTime
t
    toField (P PersistNull)            = Null -> Action
forall a. ToField a => a -> Action
PGTF.toField Null
PG.Null
    toField (P (PersistList l :: [PersistValue]
l))        = Text -> Action
forall a. ToField a => a -> Action
PGTF.toField (Text -> Action) -> Text -> Action
forall a b. (a -> b) -> a -> b
$ [PersistValue] -> Text
listToJSON [PersistValue]
l
    toField (P (PersistMap m :: [(Text, PersistValue)]
m))         = Text -> Action
forall a. ToField a => a -> Action
PGTF.toField (Text -> Action) -> Text -> Action
forall a b. (a -> b) -> a -> b
$ [(Text, PersistValue)] -> Text
mapToJSON [(Text, PersistValue)]
m
    toField (P (PersistDbSpecific s :: ConnectionString
s))  = Unknown -> Action
forall a. ToField a => a -> Action
PGTF.toField (ConnectionString -> Unknown
Unknown ConnectionString
s)
    toField (P (PersistArray a :: [PersistValue]
a))       = PGArray P -> Action
forall a. ToField a => a -> Action
PGTF.toField (PGArray P -> Action) -> PGArray P -> Action
forall a b. (a -> b) -> a -> b
$ [P] -> PGArray P
forall a. [a] -> PGArray a
PG.PGArray ([P] -> PGArray P) -> [P] -> PGArray P
forall a b. (a -> b) -> a -> b
$ PersistValue -> P
P (PersistValue -> P) -> [PersistValue] -> [P]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [PersistValue]
a
    toField (P (PersistObjectId _))    =
        String -> Action
forall a. HasCallStack => String -> a
error "Refusing to serialize a PersistObjectId to a PostgreSQL value"

newtype Unknown = Unknown { Unknown -> ConnectionString
unUnknown :: ByteString }
  deriving (Unknown -> Unknown -> Bool
(Unknown -> Unknown -> Bool)
-> (Unknown -> Unknown -> Bool) -> Eq Unknown
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Unknown -> Unknown -> Bool
$c/= :: Unknown -> Unknown -> Bool
== :: Unknown -> Unknown -> Bool
$c== :: Unknown -> Unknown -> Bool
Eq, Int -> Unknown -> ShowS
[Unknown] -> ShowS
Unknown -> String
(Int -> Unknown -> ShowS)
-> (Unknown -> String) -> ([Unknown] -> ShowS) -> Show Unknown
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Unknown] -> ShowS
$cshowList :: [Unknown] -> ShowS
show :: Unknown -> String
$cshow :: Unknown -> String
showsPrec :: Int -> Unknown -> ShowS
$cshowsPrec :: Int -> Unknown -> ShowS
Show, ReadPrec [Unknown]
ReadPrec Unknown
Int -> ReadS Unknown
ReadS [Unknown]
(Int -> ReadS Unknown)
-> ReadS [Unknown]
-> ReadPrec Unknown
-> ReadPrec [Unknown]
-> Read Unknown
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Unknown]
$creadListPrec :: ReadPrec [Unknown]
readPrec :: ReadPrec Unknown
$creadPrec :: ReadPrec Unknown
readList :: ReadS [Unknown]
$creadList :: ReadS [Unknown]
readsPrec :: Int -> ReadS Unknown
$creadsPrec :: Int -> ReadS Unknown
Read, Eq Unknown
Eq Unknown =>
(Unknown -> Unknown -> Ordering)
-> (Unknown -> Unknown -> Bool)
-> (Unknown -> Unknown -> Bool)
-> (Unknown -> Unknown -> Bool)
-> (Unknown -> Unknown -> Bool)
-> (Unknown -> Unknown -> Unknown)
-> (Unknown -> Unknown -> Unknown)
-> Ord Unknown
Unknown -> Unknown -> Bool
Unknown -> Unknown -> Ordering
Unknown -> Unknown -> Unknown
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Unknown -> Unknown -> Unknown
$cmin :: Unknown -> Unknown -> Unknown
max :: Unknown -> Unknown -> Unknown
$cmax :: Unknown -> Unknown -> Unknown
>= :: Unknown -> Unknown -> Bool
$c>= :: Unknown -> Unknown -> Bool
> :: Unknown -> Unknown -> Bool
$c> :: Unknown -> Unknown -> Bool
<= :: Unknown -> Unknown -> Bool
$c<= :: Unknown -> Unknown -> Bool
< :: Unknown -> Unknown -> Bool
$c< :: Unknown -> Unknown -> Bool
compare :: Unknown -> Unknown -> Ordering
$ccompare :: Unknown -> Unknown -> Ordering
$cp1Ord :: Eq Unknown
Ord, Typeable)

instance PGFF.FromField Unknown where
    fromField :: FieldParser Unknown
fromField f :: Field
f mdata :: Maybe ConnectionString
mdata =
      case Maybe ConnectionString
mdata of
        Nothing  -> (String -> Maybe Oid -> String -> String -> String -> ResultError)
-> Field -> String -> Conversion Unknown
forall a err.
(Typeable a, Exception err) =>
(String -> Maybe Oid -> String -> String -> String -> err)
-> Field -> String -> Conversion a
PGFF.returnError String -> Maybe Oid -> String -> String -> String -> ResultError
PGFF.UnexpectedNull Field
f "Database.Persist.Postgresql/PGFF.FromField Unknown"
        Just dat :: ConnectionString
dat -> Unknown -> Conversion Unknown
forall (m :: * -> *) a. Monad m => a -> m a
return (ConnectionString -> Unknown
Unknown ConnectionString
dat)

instance PGTF.ToField Unknown where
    toField :: Unknown -> Action
toField (Unknown a :: ConnectionString
a) = ConnectionString -> Action
PGTF.Escape ConnectionString
a

type Getter a = PGFF.FieldParser a

convertPV :: PGFF.FromField a => (a -> b) -> Getter b
convertPV :: (a -> b) -> Getter b
convertPV f :: a -> b
f = ((a -> b) -> Conversion a -> Conversion b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (Conversion a -> Conversion b)
-> (Maybe ConnectionString -> Conversion a)
-> Maybe ConnectionString
-> Conversion b
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Maybe ConnectionString -> Conversion a)
 -> Maybe ConnectionString -> Conversion b)
-> (Field -> Maybe ConnectionString -> Conversion a) -> Getter b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Field -> Maybe ConnectionString -> Conversion a
forall a. FromField a => FieldParser a
PGFF.fromField

builtinGetters :: I.IntMap (Getter PersistValue)
builtinGetters :: IntMap (Getter PersistValue)
builtinGetters = [(Int, Getter PersistValue)] -> IntMap (Getter PersistValue)
forall a. [(Int, a)] -> IntMap a
I.fromList
    [ (TypeInfo -> Int
k TypeInfo
PS.bool,        (Bool -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Bool -> PersistValue
PersistBool)
    , (TypeInfo -> Int
k TypeInfo
PS.bytea,       (Binary ConnectionString -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV (ConnectionString -> PersistValue
PersistByteString (ConnectionString -> PersistValue)
-> (Binary ConnectionString -> ConnectionString)
-> Binary ConnectionString
-> PersistValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Binary ConnectionString -> ConnectionString
forall a. Binary a -> a
unBinary))
    , (TypeInfo -> Int
k TypeInfo
PS.char,        (Text -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Text -> PersistValue
PersistText)
    , (TypeInfo -> Int
k TypeInfo
PS.name,        (Text -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Text -> PersistValue
PersistText)
    , (TypeInfo -> Int
k TypeInfo
PS.int8,        (Int64 -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Int64 -> PersistValue
PersistInt64)
    , (TypeInfo -> Int
k TypeInfo
PS.int2,        (Int64 -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Int64 -> PersistValue
PersistInt64)
    , (TypeInfo -> Int
k TypeInfo
PS.int4,        (Int64 -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Int64 -> PersistValue
PersistInt64)
    , (TypeInfo -> Int
k TypeInfo
PS.text,        (Text -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Text -> PersistValue
PersistText)
    , (TypeInfo -> Int
k TypeInfo
PS.xml,         (Text -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Text -> PersistValue
PersistText)
    , (TypeInfo -> Int
k TypeInfo
PS.float4,      (Double -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Double -> PersistValue
PersistDouble)
    , (TypeInfo -> Int
k TypeInfo
PS.float8,      (Double -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Double -> PersistValue
PersistDouble)
    , (TypeInfo -> Int
k TypeInfo
PS.money,       (Rational -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Rational -> PersistValue
PersistRational)
    , (TypeInfo -> Int
k TypeInfo
PS.bpchar,      (Text -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Text -> PersistValue
PersistText)
    , (TypeInfo -> Int
k TypeInfo
PS.varchar,     (Text -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Text -> PersistValue
PersistText)
    , (TypeInfo -> Int
k TypeInfo
PS.date,        (Day -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Day -> PersistValue
PersistDay)
    , (TypeInfo -> Int
k TypeInfo
PS.time,        (TimeOfDay -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV TimeOfDay -> PersistValue
PersistTimeOfDay)
    , (TypeInfo -> Int
k TypeInfo
PS.timestamp,   (LocalTime -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV (UTCTime -> PersistValue
PersistUTCTime(UTCTime -> PersistValue)
-> (LocalTime -> UTCTime) -> LocalTime -> PersistValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TimeZone -> LocalTime -> UTCTime
localTimeToUTC TimeZone
utc))
    , (TypeInfo -> Int
k TypeInfo
PS.timestamptz, (UTCTime -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV UTCTime -> PersistValue
PersistUTCTime)
    , (TypeInfo -> Int
k TypeInfo
PS.bit,         (Int64 -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Int64 -> PersistValue
PersistInt64)
    , (TypeInfo -> Int
k TypeInfo
PS.varbit,      (Int64 -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Int64 -> PersistValue
PersistInt64)
    , (TypeInfo -> Int
k TypeInfo
PS.numeric,     (Rational -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV Rational -> PersistValue
PersistRational)
    , (TypeInfo -> Int
k TypeInfo
PS.void,        \_ _ -> PersistValue -> Conversion PersistValue
forall (m :: * -> *) a. Monad m => a -> m a
return PersistValue
PersistNull)
    , (TypeInfo -> Int
k TypeInfo
PS.json,        (Unknown -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV (ConnectionString -> PersistValue
PersistByteString (ConnectionString -> PersistValue)
-> (Unknown -> ConnectionString) -> Unknown -> PersistValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unknown -> ConnectionString
unUnknown))
    , (TypeInfo -> Int
k TypeInfo
PS.jsonb,       (Unknown -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV (ConnectionString -> PersistValue
PersistByteString (ConnectionString -> PersistValue)
-> (Unknown -> ConnectionString) -> Unknown -> PersistValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unknown -> ConnectionString
unUnknown))
    , (TypeInfo -> Int
k TypeInfo
PS.unknown,     (Unknown -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV (ConnectionString -> PersistValue
PersistByteString (ConnectionString -> PersistValue)
-> (Unknown -> ConnectionString) -> Unknown -> PersistValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unknown -> ConnectionString
unUnknown))

    -- Array types: same order as above.
    -- The OIDs were taken from pg_type.
    , (1000,             (Bool -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Bool -> PersistValue
PersistBool)
    , (1001,             (Binary ConnectionString -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf (ConnectionString -> PersistValue
PersistByteString (ConnectionString -> PersistValue)
-> (Binary ConnectionString -> ConnectionString)
-> Binary ConnectionString
-> PersistValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Binary ConnectionString -> ConnectionString
forall a. Binary a -> a
unBinary))
    , (1002,             (Text -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Text -> PersistValue
PersistText)
    , (1003,             (Text -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Text -> PersistValue
PersistText)
    , (1016,             (Int64 -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Int64 -> PersistValue
PersistInt64)
    , (1005,             (Int64 -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Int64 -> PersistValue
PersistInt64)
    , (1007,             (Int64 -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Int64 -> PersistValue
PersistInt64)
    , (1009,             (Text -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Text -> PersistValue
PersistText)
    , (143,              (Text -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Text -> PersistValue
PersistText)
    , (1021,             (Double -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Double -> PersistValue
PersistDouble)
    , (1022,             (Double -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Double -> PersistValue
PersistDouble)
    , (1023,             (UTCTime -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf UTCTime -> PersistValue
PersistUTCTime)
    , (1024,             (UTCTime -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf UTCTime -> PersistValue
PersistUTCTime)
    , (791,              (Rational -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Rational -> PersistValue
PersistRational)
    , (1014,             (Text -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Text -> PersistValue
PersistText)
    , (1015,             (Text -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Text -> PersistValue
PersistText)
    , (1182,             (Day -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Day -> PersistValue
PersistDay)
    , (1183,             (TimeOfDay -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf TimeOfDay -> PersistValue
PersistTimeOfDay)
    , (1115,             (UTCTime -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf UTCTime -> PersistValue
PersistUTCTime)
    , (1185,             (UTCTime -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf UTCTime -> PersistValue
PersistUTCTime)
    , (1561,             (Int64 -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Int64 -> PersistValue
PersistInt64)
    , (1563,             (Int64 -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Int64 -> PersistValue
PersistInt64)
    , (1231,             (Rational -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf Rational -> PersistValue
PersistRational)
    -- no array(void) type
    , (2951,             (Unknown -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf (ConnectionString -> PersistValue
PersistDbSpecific (ConnectionString -> PersistValue)
-> (Unknown -> ConnectionString) -> Unknown -> PersistValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unknown -> ConnectionString
unUnknown))
    , (199,              (Unknown -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf (ConnectionString -> PersistValue
PersistByteString (ConnectionString -> PersistValue)
-> (Unknown -> ConnectionString) -> Unknown -> PersistValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unknown -> ConnectionString
unUnknown))
    , (3807,             (Unknown -> PersistValue) -> Getter PersistValue
forall a.
(FromField a, Typeable a) =>
(a -> PersistValue) -> Getter PersistValue
listOf (ConnectionString -> PersistValue
PersistByteString (ConnectionString -> PersistValue)
-> (Unknown -> ConnectionString) -> Unknown -> PersistValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unknown -> ConnectionString
unUnknown))
    -- no array(unknown) either
    ]
    where
        k :: TypeInfo -> Int
k (TypeInfo -> Oid
PGFF.typoid -> Oid
i) = Oid -> Int
PG.oid2int Oid
i
        -- A @listOf f@ will use a @PGArray (Maybe T)@ to convert
        -- the values to Haskell-land.  The @Maybe@ is important
        -- because the usual way of checking NULLs
        -- (c.f. withStmt') won't check for NULL inside
        -- arrays---or any other compound structure for that matter.
        listOf :: (a -> PersistValue) -> Getter PersistValue
listOf f :: a -> PersistValue
f = (PGArray (Maybe a) -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV ([PersistValue] -> PersistValue
PersistList ([PersistValue] -> PersistValue)
-> (PGArray (Maybe a) -> [PersistValue])
-> PGArray (Maybe a)
-> PersistValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe a -> PersistValue) -> [Maybe a] -> [PersistValue]
forall a b. (a -> b) -> [a] -> [b]
map ((a -> PersistValue) -> Maybe a -> PersistValue
forall a. (a -> PersistValue) -> Maybe a -> PersistValue
nullable a -> PersistValue
f) ([Maybe a] -> [PersistValue])
-> (PGArray (Maybe a) -> [Maybe a])
-> PGArray (Maybe a)
-> [PersistValue]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PGArray (Maybe a) -> [Maybe a]
forall a. PGArray a -> [a]
PG.fromPGArray)
          where nullable :: (a -> PersistValue) -> Maybe a -> PersistValue
nullable = PersistValue -> (a -> PersistValue) -> Maybe a -> PersistValue
forall b a. b -> (a -> b) -> Maybe a -> b
maybe PersistValue
PersistNull

getGetter :: PG.Connection -> PG.Oid -> Getter PersistValue
getGetter :: Connection -> Oid -> Getter PersistValue
getGetter _conn :: Connection
_conn oid :: Oid
oid
  = Getter PersistValue
-> Maybe (Getter PersistValue) -> Getter PersistValue
forall a. a -> Maybe a -> a
fromMaybe Getter PersistValue
defaultGetter (Maybe (Getter PersistValue) -> Getter PersistValue)
-> Maybe (Getter PersistValue) -> Getter PersistValue
forall a b. (a -> b) -> a -> b
$ Int -> IntMap (Getter PersistValue) -> Maybe (Getter PersistValue)
forall a. Int -> IntMap a -> Maybe a
I.lookup (Oid -> Int
PG.oid2int Oid
oid) IntMap (Getter PersistValue)
builtinGetters
  where defaultGetter :: Getter PersistValue
defaultGetter = (Unknown -> PersistValue) -> Getter PersistValue
forall a b. FromField a => (a -> b) -> Getter b
convertPV (ConnectionString -> PersistValue
PersistDbSpecific (ConnectionString -> PersistValue)
-> (Unknown -> ConnectionString) -> Unknown -> PersistValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unknown -> ConnectionString
unUnknown)

unBinary :: PG.Binary a -> a
unBinary :: Binary a -> a
unBinary (PG.Binary x :: a
x) = a
x

doesTableExist :: (Text -> IO Statement)
               -> DBName -- ^ table name
               -> IO Bool
doesTableExist :: (Text -> IO Statement) -> DBName -> IO Bool
doesTableExist getter :: Text -> IO Statement
getter (DBName name :: 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) (\src :: 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 = "SELECT COUNT(*) FROM pg_catalog.pg_tables WHERE schemaname != 'pg_catalog'"
          Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> " 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 "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 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 1] = Bool -> ConduitT a o m Bool
forall (m :: * -> *) b a o. Monad m => b -> ConduitT a o m b
finish Bool
True
    start' res :: [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
$ "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 x :: 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 "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' allDefs :: [EntityDef]
allDefs getter :: Text -> IO Statement
getter entity :: 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 (DBName, [DBName]))]
old <- (Text -> IO Statement)
-> EntityDef
-> [Column]
-> IO [Either Text (Either Column (DBName, [DBName]))]
getColumns Text -> IO Statement
getter EntityDef
entity [Column]
newcols'
    case [Either Text (Either Column (DBName, [DBName]))]
-> ([Text], [Either Column (DBName, [DBName])])
forall a b. [Either a b] -> ([a], [b])
partitionEithers [Either Text (Either Column (DBName, [DBName]))]
old of
        ([], old'' :: [Either Column (DBName, [DBName])]
old'') -> do
            Bool
exists <-
                if [Either Text (Either Column (DBName, [DBName]))] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Either Text (Either Column (DBName, [DBName]))]
old
                    then (Text -> IO Statement) -> DBName -> IO Bool
doesTableExist Text -> IO Statement
getter DBName
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 (DBName, [DBName])] -> [AlterDB]
migrationText Bool
exists [Either Column (DBName, [DBName])]
old''
        (errs :: [Text]
errs, _) -> 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 :: DBName
name = EntityDef -> DBName
entityDB EntityDef
entity
    (newcols' :: [Column]
newcols', udefs :: [UniqueDef]
udefs, fdefs :: [ForeignDef]
fdefs) = [EntityDef] -> EntityDef -> ([Column], [UniqueDef], [ForeignDef])
mkColumns [EntityDef]
allDefs EntityDef
entity
    migrationText :: Bool -> [Either Column (DBName, [DBName])] -> [AlterDB]
migrationText exists :: Bool
exists old'' :: [Either Column (DBName, [DBName])]
old'' =
        if Bool -> Bool
not Bool
exists
            then [Column] -> [ForeignDef] -> [(DBName, [DBName])] -> [AlterDB]
createText [Column]
newcols [ForeignDef]
fdefs [(DBName, [DBName])]
udspair
            else let (acs :: [AlterColumn']
acs, ats :: [AlterTable]
ats) = [EntityDef]
-> EntityDef
-> ([Column], [(DBName, [DBName])])
-> ([Column], [(DBName, [DBName])])
-> ([AlterColumn'], [AlterTable])
getAlters [EntityDef]
allDefs EntityDef
entity ([Column]
newcols, [(DBName, [DBName])]
udspair) (([Column], [(DBName, [DBName])])
 -> ([AlterColumn'], [AlterTable]))
-> ([Column], [(DBName, [DBName])])
-> ([AlterColumn'], [AlterTable])
forall a b. (a -> b) -> a -> b
$ ([Column], [(DBName, [DBName])])
-> ([Column], [(DBName, [DBName])])
excludeForeignKeys (([Column], [(DBName, [DBName])])
 -> ([Column], [(DBName, [DBName])]))
-> ([Column], [(DBName, [DBName])])
-> ([Column], [(DBName, [DBName])])
forall a b. (a -> b) -> a -> b
$ ([Column], [(DBName, [DBName])])
old'
                     acs' :: [AlterDB]
acs' = (AlterColumn' -> AlterDB) -> [AlterColumn'] -> [AlterDB]
forall a b. (a -> b) -> [a] -> [b]
map (DBName -> AlterColumn' -> AlterDB
AlterColumn DBName
name) [AlterColumn']
acs
                     ats' :: [AlterDB]
ats' = (AlterTable -> AlterDB) -> [AlterTable] -> [AlterDB]
forall a b. (a -> b) -> [a] -> [b]
map (DBName -> AlterTable -> AlterDB
AlterTable DBName
name) [AlterTable]
ats
                 in  [AlterDB]
acs' [AlterDB] -> [AlterDB] -> [AlterDB]
forall a. [a] -> [a] -> [a]
++ [AlterDB]
ats'
       where
         old' :: ([Column], [(DBName, [DBName])])
old' = [Either Column (DBName, [DBName])]
-> ([Column], [(DBName, [DBName])])
forall a b. [Either a b] -> ([a], [b])
partitionEithers [Either Column (DBName, [DBName])]
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 -> DBName -> Bool
safeToRemove EntityDef
entity (DBName -> Bool) -> (Column -> DBName) -> Column -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Column -> DBName
cName) [Column]
newcols'
         udspair :: [(DBName, [DBName])]
udspair = (UniqueDef -> (DBName, [DBName]))
-> [UniqueDef] -> [(DBName, [DBName])]
forall a b. (a -> b) -> [a] -> [b]
map UniqueDef -> (DBName, [DBName])
udToPair [UniqueDef]
udefs
         excludeForeignKeys :: ([Column], [(DBName, [DBName])])
-> ([Column], [(DBName, [DBName])])
excludeForeignKeys (xs :: [Column]
xs,ys :: [(DBName, [DBName])]
ys) = ((Column -> Column) -> [Column] -> [Column]
forall a b. (a -> b) -> [a] -> [b]
map Column -> Column
excludeForeignKey [Column]
xs,[(DBName, [DBName])]
ys)
         excludeForeignKey :: Column -> Column
excludeForeignKey c :: Column
c = case Column -> Maybe (DBName, DBName)
cReference Column
c of
           Just (_,fk :: DBName
fk) ->
             case (ForeignDef -> Bool) -> [ForeignDef] -> Maybe ForeignDef
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\f :: ForeignDef
f -> DBName
fk DBName -> DBName -> Bool
forall a. Eq a => a -> a -> Bool
== ForeignDef -> DBName
foreignConstraintNameDBName ForeignDef
f) [ForeignDef]
fdefs of
               Just _ -> Column
c { cReference :: Maybe (DBName, DBName)
cReference = Maybe (DBName, DBName)
forall a. Maybe a
Nothing }
               Nothing -> Column
c
           Nothing -> Column
c
            -- Check for table existence if there are no columns, workaround
            -- for https://github.com/yesodweb/persistent/issues/152

    createText :: [Column] -> [ForeignDef] -> [(DBName, [DBName])] -> [AlterDB]
createText newcols :: [Column]
newcols fdefs :: [ForeignDef]
fdefs udspair :: [(DBName, [DBName])]
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 = (((DBName, [DBName]) -> [AlterDB])
 -> [(DBName, [DBName])] -> [AlterDB])
-> [(DBName, [DBName])]
-> ((DBName, [DBName]) -> [AlterDB])
-> [AlterDB]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((DBName, [DBName]) -> [AlterDB])
-> [(DBName, [DBName])] -> [AlterDB]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap [(DBName, [DBName])]
udspair (((DBName, [DBName]) -> [AlterDB]) -> [AlterDB])
-> ((DBName, [DBName]) -> [AlterDB]) -> [AlterDB]
forall a b. (a -> b) -> a -> b
$ \(uname :: DBName
uname, ucols :: [DBName]
ucols) ->
                [DBName -> AlterTable -> AlterDB
AlterTable DBName
name (AlterTable -> AlterDB) -> AlterTable -> AlterDB
forall a b. (a -> b) -> a -> b
$ DBName -> [DBName] -> AlterTable
AddUniqueConstraint DBName
uname [DBName]
ucols]
        references :: [AlterDB]
references = (Column -> Maybe AlterDB) -> [Column] -> [AlterDB]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (\c :: Column
c@Column { cName :: Column -> DBName
cName=DBName
cname, cReference :: Column -> Maybe (DBName, DBName)
cReference=Just (refTblName :: DBName
refTblName, _) } ->
            [EntityDef]
-> DBName
-> DBName
-> DBName
-> Maybe (DBName, DBName)
-> Maybe AlterDB
getAddReference [EntityDef]
allDefs DBName
name DBName
refTblName DBName
cname (Column -> Maybe (DBName, DBName)
cReference Column
c))
                   ([Column] -> [AlterDB]) -> [Column] -> [AlterDB]
forall a b. (a -> b) -> a -> b
$ (Column -> Bool) -> [Column] -> [Column]
forall a. (a -> Bool) -> [a] -> [a]
filter (Maybe (DBName, DBName) -> Bool
forall a. Maybe a -> Bool
isJust (Maybe (DBName, DBName) -> Bool)
-> (Column -> Maybe (DBName, DBName)) -> Column -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Column -> Maybe (DBName, DBName)
cReference) [Column]
newcols
        foreignsAlt :: [AlterDB]
foreignsAlt = ((ForeignDef -> AlterDB) -> [ForeignDef] -> [AlterDB])
-> [ForeignDef] -> (ForeignDef -> AlterDB) -> [AlterDB]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (ForeignDef -> AlterDB) -> [ForeignDef] -> [AlterDB]
forall a b. (a -> b) -> [a] -> [b]
map [ForeignDef]
fdefs (\fdef :: ForeignDef
fdef ->
            let (childfields :: [DBName]
childfields, parentfields :: [DBName]
parentfields) = [(DBName, DBName)] -> ([DBName], [DBName])
forall a b. [(a, b)] -> ([a], [b])
unzip ((((HaskellName, DBName), (HaskellName, DBName))
 -> (DBName, DBName))
-> [((HaskellName, DBName), (HaskellName, DBName))]
-> [(DBName, DBName)]
forall a b. (a -> b) -> [a] -> [b]
map (\((_,b :: DBName
b),(_,d :: DBName
d)) -> (DBName
b,DBName
d)) (ForeignDef -> [((HaskellName, DBName), (HaskellName, DBName))]
foreignFields ForeignDef
fdef))
            in DBName -> AlterColumn' -> AlterDB
AlterColumn DBName
name (ForeignDef -> DBName
foreignRefTableDBName ForeignDef
fdef, DBName -> [DBName] -> [Text] -> AlterColumn
AddReference (ForeignDef -> DBName
foreignConstraintNameDBName ForeignDef
fdef) [DBName]
childfields ((DBName -> Text) -> [DBName] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map DBName -> Text
escape [DBName]
parentfields)))

addTable :: [Column] -> EntityDef -> AlterDB
addTable :: [Column] -> EntityDef -> AlterDB
addTable cols :: [Column]
cols entity :: 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
                       [ "CREATe TABLE " -- DO NOT FIX THE CAPITALIZATION!
                       , DBName -> Text
escape DBName
name
                       , "("
                       , Text
idtxt
                       , if [Column] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Column]
cols then "" else ","
                       , Text -> [Text] -> Text
T.intercalate "," ([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]
cols
                       , ")"
                       ]
    where
      name :: DBName
name = EntityDef -> DBName
entityDB EntityDef
entity
      idtxt :: Text
idtxt = case EntityDef -> Maybe CompositeDef
entityPrimary EntityDef
entity of
                Just pdef :: CompositeDef
pdef -> [Text] -> Text
T.concat [" PRIMARY KEY (", Text -> [Text] -> Text
T.intercalate "," ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (FieldDef -> Text) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (DBName -> Text
escape (DBName -> Text) -> (FieldDef -> DBName) -> FieldDef -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldDef -> DBName
fieldDB) ([FieldDef] -> [Text]) -> [FieldDef] -> [Text]
forall a b. (a -> b) -> a -> b
$ CompositeDef -> [FieldDef]
compositeFields CompositeDef
pdef, ")"]
                Nothing   ->
                    let defText :: Maybe Text
defText = [Text] -> Maybe Text
defaultAttribute ([Text] -> Maybe Text) -> [Text] -> Maybe Text
forall a b. (a -> b) -> a -> b
$ FieldDef -> [Text]
fieldAttrs (FieldDef -> [Text]) -> FieldDef -> [Text]
forall a b. (a -> b) -> a -> b
$ EntityDef -> FieldDef
entityId EntityDef
entity
                        sType :: SqlType
sType = FieldDef -> SqlType
fieldSqlType (FieldDef -> SqlType) -> FieldDef -> SqlType
forall a b. (a -> b) -> a -> b
$ EntityDef -> FieldDef
entityId EntityDef
entity
                    in  [Text] -> Text
T.concat
                            [ DBName -> Text
escape (DBName -> Text) -> DBName -> Text
forall a b. (a -> b) -> a -> b
$ FieldDef -> DBName
fieldDB (EntityDef -> FieldDef
entityId EntityDef
entity)
                            , SqlType -> Maybe Text -> Text
maySerial SqlType
sType Maybe Text
defText
                            , " PRIMARY KEY UNIQUE"
                            , Maybe Text -> Text
mayDefault Maybe Text
defText
                            ]

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

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

type SafeToRemove = Bool

data AlterColumn = ChangeType SqlType Text
                 | IsNull | NotNull | Add' Column | Drop SafeToRemove
                 | Default Text | NoDefault | Update' Text
                 | AddReference DBName [DBName] [Text] | DropReference DBName
type AlterColumn' = (DBName, AlterColumn)

data AlterTable = AddUniqueConstraint DBName [DBName]
                | DropConstraint DBName

data AlterDB = AddTable Text
             | AlterColumn DBName AlterColumn'
             | AlterTable DBName AlterTable

-- | Returns all of the columns in the given table currently in the database.
getColumns :: (Text -> IO Statement)
           -> EntityDef -> [Column]
           -> IO [Either Text (Either Column (DBName, [DBName]))]
getColumns :: (Text -> IO Statement)
-> EntityDef
-> [Column]
-> IO [Either Text (Either Column (DBName, [DBName]))]
getColumns getter :: Text -> IO Statement
getter def :: EntityDef
def cols :: [Column]
cols = do
    let sqlv :: Text
sqlv=[Text] -> Text
T.concat ["SELECT "
                          ,"column_name "
                          ,",is_nullable "
                          ,",COALESCE(domain_name, udt_name)" -- See DOMAINS below
                          ,",column_default "
                          ,",numeric_precision "
                          ,",numeric_scale "
                          ,",character_maximum_length "
                          ,"FROM information_schema.columns "
                          ,"WHERE table_catalog=current_database() "
                          ,"AND table_schema=current_schema() "
                          ,"AND table_name=? "
                          ,"AND column_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
$ DBName -> Text
unDBName (DBName -> Text) -> DBName -> Text
forall a b. (a -> b) -> a -> b
$ EntityDef -> DBName
entityDB EntityDef
def
            , Text -> PersistValue
PersistText (Text -> PersistValue) -> Text -> PersistValue
forall a b. (a -> b) -> a -> b
$ DBName -> Text
unDBName (DBName -> Text) -> DBName -> Text
forall a b. (a -> b) -> a -> b
$ FieldDef -> DBName
fieldDB (EntityDef -> FieldDef
entityId EntityDef
def)
            ]
    [Either Text (Either Column (DBName, [DBName]))]
cs <- Acquire (ConduitM () [PersistValue] IO ())
-> (ConduitM () [PersistValue] IO ()
    -> IO [Either Text (Either Column (DBName, [DBName]))])
-> IO [Either Text (Either Column (DBName, [DBName]))]
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) (\src :: ConduitM () [PersistValue] IO ()
src -> ConduitT
  () Void IO [Either Text (Either Column (DBName, [DBName]))]
-> IO [Either Text (Either Column (DBName, [DBName]))]
forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit (ConduitT
   () Void IO [Either Text (Either Column (DBName, [DBName]))]
 -> IO [Either Text (Either Column (DBName, [DBName]))])
-> ConduitT
     () Void IO [Either Text (Either Column (DBName, [DBName]))]
-> IO [Either Text (Either Column (DBName, [DBName]))]
forall a b. (a -> b) -> a -> b
$ ConduitM () [PersistValue] IO ()
src ConduitM () [PersistValue] IO ()
-> ConduitM
     [PersistValue]
     Void
     IO
     [Either Text (Either Column (DBName, [DBName]))]
-> ConduitT
     () Void IO [Either Text (Either Column (DBName, [DBName]))]
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 (DBName, [DBName]))]
helper)
    let sqlc :: Text
sqlc = [Text] -> Text
T.concat ["SELECT "
                          ,"c.constraint_name, "
                          ,"c.column_name "
                          ,"FROM information_schema.key_column_usage c, "
                          ,"information_schema.table_constraints k "
                          ,"WHERE c.table_catalog=current_database() "
                          ,"AND c.table_catalog=k.table_catalog "
                          ,"AND c.table_schema=current_schema() "
                          ,"AND c.table_schema=k.table_schema "
                          ,"AND c.table_name=? "
                          ,"AND c.table_name=k.table_name "
                          ,"AND c.column_name <> ? "
                          ,"AND c.constraint_name=k.constraint_name "
                          ,"AND NOT k.constraint_type IN ('PRIMARY KEY', 'FOREIGN KEY') "
                          ,"ORDER BY c.constraint_name, c.column_name"]

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

    [Either Text (Either Column (DBName, [DBName]))]
us <- Acquire (ConduitM () [PersistValue] IO ())
-> (ConduitM () [PersistValue] IO ()
    -> IO [Either Text (Either Column (DBName, [DBName]))])
-> IO [Either Text (Either Column (DBName, [DBName]))]
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) (\src :: ConduitM () [PersistValue] IO ()
src -> ConduitT
  () Void IO [Either Text (Either Column (DBName, [DBName]))]
-> IO [Either Text (Either Column (DBName, [DBName]))]
forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit (ConduitT
   () Void IO [Either Text (Either Column (DBName, [DBName]))]
 -> IO [Either Text (Either Column (DBName, [DBName]))])
-> ConduitT
     () Void IO [Either Text (Either Column (DBName, [DBName]))]
-> IO [Either Text (Either Column (DBName, [DBName]))]
forall a b. (a -> b) -> a -> b
$ ConduitM () [PersistValue] IO ()
src ConduitM () [PersistValue] IO ()
-> ConduitM
     [PersistValue]
     Void
     IO
     [Either Text (Either Column (DBName, [DBName]))]
-> ConduitT
     () Void IO [Either Text (Either Column (DBName, [DBName]))]
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 (DBName, [DBName]))]
forall o a a.
ConduitT
  [PersistValue] o IO [Either a (Either a (DBName, [DBName]))]
helperU)
    [Either Text (Either Column (DBName, [DBName]))]
-> IO [Either Text (Either Column (DBName, [DBName]))]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Either Text (Either Column (DBName, [DBName]))]
 -> IO [Either Text (Either Column (DBName, [DBName]))])
-> [Either Text (Either Column (DBName, [DBName]))]
-> IO [Either Text (Either Column (DBName, [DBName]))]
forall a b. (a -> b) -> a -> b
$ [Either Text (Either Column (DBName, [DBName]))]
cs [Either Text (Either Column (DBName, [DBName]))]
-> [Either Text (Either Column (DBName, [DBName]))]
-> [Either Text (Either Column (DBName, [DBName]))]
forall a. [a] -> [a] -> [a]
++ [Either Text (Either Column (DBName, [DBName]))]
us
  where
    refMap :: Map Text (DBName, DBName)
refMap = [(Text, (DBName, DBName))] -> Map Text (DBName, DBName)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(Text, (DBName, DBName))] -> Map Text (DBName, DBName))
-> [(Text, (DBName, DBName))] -> Map Text (DBName, DBName)
forall a b. (a -> b) -> a -> b
$ ([(Text, (DBName, DBName))]
 -> Column -> [(Text, (DBName, DBName))])
-> [(Text, (DBName, DBName))]
-> [Column]
-> [(Text, (DBName, DBName))]
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl [(Text, (DBName, DBName))] -> Column -> [(Text, (DBName, DBName))]
ref [] [Column]
cols
        where ref :: [(Text, (DBName, DBName))] -> Column -> [(Text, (DBName, DBName))]
ref rs :: [(Text, (DBName, DBName))]
rs c :: Column
c = case Column -> Maybe (DBName, DBName)
cReference Column
c of
                  Nothing -> [(Text, (DBName, DBName))]
rs
                  (Just r :: (DBName, DBName)
r) -> (DBName -> Text
unDBName (DBName -> Text) -> DBName -> Text
forall a b. (a -> b) -> a -> b
$ Column -> DBName
cName Column
c, (DBName, DBName)
r) (Text, (DBName, DBName))
-> [(Text, (DBName, DBName))] -> [(Text, (DBName, DBName))]
forall a. a -> [a] -> [a]
: [(Text, (DBName, DBName))]
rs
    getAll :: ([(Text, Text)] -> c) -> ConduitT [PersistValue] o m c
getAll front :: [(Text, Text)] -> c
front = do
        Maybe [PersistValue]
x <- ConduitT [PersistValue] o m (Maybe [PersistValue])
forall (m :: * -> *) a o. Monad m => ConduitT a o m (Maybe a)
CL.head
        case Maybe [PersistValue]
x of
            Nothing -> c -> ConduitT [PersistValue] o m c
forall (m :: * -> *) a. Monad m => a -> m a
return (c -> ConduitT [PersistValue] o m c)
-> c -> ConduitT [PersistValue] o m c
forall a b. (a -> b) -> a -> b
$ [(Text, Text)] -> c
front []
            Just [PersistText con :: Text
con, PersistText col :: Text
col] -> ([(Text, Text)] -> c) -> ConduitT [PersistValue] o m c
getAll ([(Text, Text)] -> c
front ([(Text, Text)] -> c)
-> ([(Text, Text)] -> [(Text, Text)]) -> [(Text, Text)] -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:) (Text
con, Text
col))
            Just [PersistByteString con :: ConnectionString
con, PersistByteString col :: ConnectionString
col] -> ([(Text, Text)] -> c) -> ConduitT [PersistValue] o m c
getAll ([(Text, Text)] -> c
front ([(Text, Text)] -> c)
-> ([(Text, Text)] -> [(Text, Text)]) -> [(Text, Text)] -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:) (ConnectionString -> Text
T.decodeUtf8 ConnectionString
con, ConnectionString -> Text
T.decodeUtf8 ConnectionString
col))
            Just o :: [PersistValue]
o -> String -> ConduitT [PersistValue] o m c
forall a. HasCallStack => String -> a
error (String -> ConduitT [PersistValue] o m c)
-> String -> ConduitT [PersistValue] o m c
forall a b. (a -> b) -> a -> b
$ "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 :: ConduitT
  [PersistValue] o IO [Either a (Either a (DBName, [DBName]))]
helperU = do
        [(Text, Text)]
rows <- ([(Text, Text)] -> [(Text, Text)])
-> ConduitT [PersistValue] o IO [(Text, Text)]
forall (m :: * -> *) c o.
Monad m =>
([(Text, Text)] -> c) -> ConduitT [PersistValue] o m c
getAll [(Text, Text)] -> [(Text, Text)]
forall a. a -> a
id
        [Either a (Either a (DBName, [DBName]))]
-> ConduitT
     [PersistValue] o IO [Either a (Either a (DBName, [DBName]))]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Either a (Either a (DBName, [DBName]))]
 -> ConduitT
      [PersistValue] o IO [Either a (Either a (DBName, [DBName]))])
-> [Either a (Either a (DBName, [DBName]))]
-> ConduitT
     [PersistValue] o IO [Either a (Either a (DBName, [DBName]))]
forall a b. (a -> b) -> a -> b
$ ([(Text, Text)] -> Either a (Either a (DBName, [DBName])))
-> [[(Text, Text)]] -> [Either a (Either a (DBName, [DBName]))]
forall a b. (a -> b) -> [a] -> [b]
map (Either a (DBName, [DBName])
-> Either a (Either a (DBName, [DBName]))
forall a b. b -> Either a b
Right (Either a (DBName, [DBName])
 -> Either a (Either a (DBName, [DBName])))
-> ([(Text, Text)] -> Either a (DBName, [DBName]))
-> [(Text, Text)]
-> Either a (Either a (DBName, [DBName]))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DBName, [DBName]) -> Either a (DBName, [DBName])
forall a b. b -> Either a b
Right ((DBName, [DBName]) -> Either a (DBName, [DBName]))
-> ([(Text, Text)] -> (DBName, [DBName]))
-> [(Text, Text)]
-> Either a (DBName, [DBName])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> DBName
DBName (Text -> DBName)
-> ([(Text, Text)] -> Text) -> [(Text, Text)] -> DBName
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)] -> DBName)
-> ([(Text, Text)] -> [DBName])
-> [(Text, Text)]
-> (DBName, [DBName])
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& ((Text, Text) -> DBName) -> [(Text, Text)] -> [DBName]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> DBName
DBName (Text -> DBName)
-> ((Text, Text) -> Text) -> (Text, Text) -> DBName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Text) -> Text
forall a b. (a, b) -> b
snd)))
               ([[(Text, Text)]] -> [Either a (Either a (DBName, [DBName]))])
-> [[(Text, Text)]] -> [Either a (Either a (DBName, [DBName]))]
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
    helper :: ConduitM
  [PersistValue]
  Void
  IO
  [Either Text (Either Column (DBName, [DBName]))]
helper = do
        Maybe [PersistValue]
x <- ConduitT [PersistValue] Void IO (Maybe [PersistValue])
forall (m :: * -> *) a o. Monad m => ConduitT a o m (Maybe a)
CL.head
        case Maybe [PersistValue]
x of
            Nothing -> [Either Text (Either Column (DBName, [DBName]))]
-> ConduitM
     [PersistValue]
     Void
     IO
     [Either Text (Either Column (DBName, [DBName]))]
forall (m :: * -> *) a. Monad m => a -> m a
return []
            Just x' :: [PersistValue]
x'@((PersistText cname :: Text
cname):_) -> do
                Either Text Column
col <- IO (Either Text Column)
-> ConduitT [PersistValue] Void IO (Either Text Column)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either Text Column)
 -> ConduitT [PersistValue] Void IO (Either Text Column))
-> IO (Either Text Column)
-> ConduitT [PersistValue] Void IO (Either Text Column)
forall a b. (a -> b) -> a -> b
$ (Text -> IO Statement)
-> DBName
-> [PersistValue]
-> Maybe (DBName, DBName)
-> IO (Either Text Column)
getColumn Text -> IO Statement
getter (EntityDef -> DBName
entityDB EntityDef
def) [PersistValue]
x' (Text -> Map Text (DBName, DBName) -> Maybe (DBName, DBName)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
cname Map Text (DBName, DBName)
refMap)
                let col' :: Either Text (Either Column (DBName, [DBName]))
col' = case Either Text Column
col of
                            Left e :: Text
e -> Text -> Either Text (Either Column (DBName, [DBName]))
forall a b. a -> Either a b
Left Text
e
                            Right c :: Column
c -> Either Column (DBName, [DBName])
-> Either Text (Either Column (DBName, [DBName]))
forall a b. b -> Either a b
Right (Either Column (DBName, [DBName])
 -> Either Text (Either Column (DBName, [DBName])))
-> Either Column (DBName, [DBName])
-> Either Text (Either Column (DBName, [DBName]))
forall a b. (a -> b) -> a -> b
$ Column -> Either Column (DBName, [DBName])
forall a b. a -> Either a b
Left Column
c
                [Either Text (Either Column (DBName, [DBName]))]
cols <- ConduitM
  [PersistValue]
  Void
  IO
  [Either Text (Either Column (DBName, [DBName]))]
helper
                [Either Text (Either Column (DBName, [DBName]))]
-> ConduitM
     [PersistValue]
     Void
     IO
     [Either Text (Either Column (DBName, [DBName]))]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Either Text (Either Column (DBName, [DBName]))]
 -> ConduitM
      [PersistValue]
      Void
      IO
      [Either Text (Either Column (DBName, [DBName]))])
-> [Either Text (Either Column (DBName, [DBName]))]
-> ConduitM
     [PersistValue]
     Void
     IO
     [Either Text (Either Column (DBName, [DBName]))]
forall a b. (a -> b) -> a -> b
$ Either Text (Either Column (DBName, [DBName]))
col' Either Text (Either Column (DBName, [DBName]))
-> [Either Text (Either Column (DBName, [DBName]))]
-> [Either Text (Either Column (DBName, [DBName]))]
forall a. a -> [a] -> [a]
: [Either Text (Either Column (DBName, [DBName]))]
cols

-- | Check if a column name is listed as the "safe to remove" in the entity
-- list.
safeToRemove :: EntityDef -> DBName -> Bool
safeToRemove :: EntityDef -> DBName -> Bool
safeToRemove def :: EntityDef
def (DBName colName :: Text
colName)
    = (FieldDef -> Bool) -> [FieldDef] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem "SafeToRemove" ([Text] -> Bool) -> (FieldDef -> [Text]) -> FieldDef -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldDef -> [Text]
fieldAttrs)
    ([FieldDef] -> Bool) -> [FieldDef] -> Bool
forall a b. (a -> b) -> a -> b
$ (FieldDef -> Bool) -> [FieldDef] -> [FieldDef]
forall a. (a -> Bool) -> [a] -> [a]
filter ((DBName -> DBName -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> DBName
DBName Text
colName) (DBName -> Bool) -> (FieldDef -> DBName) -> FieldDef -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldDef -> DBName
fieldDB)
    ([FieldDef] -> [FieldDef]) -> [FieldDef] -> [FieldDef]
forall a b. (a -> b) -> a -> b
$ EntityDef -> [FieldDef]
entityFields EntityDef
def

getAlters :: [EntityDef]
          -> EntityDef
          -> ([Column], [(DBName, [DBName])])
          -> ([Column], [(DBName, [DBName])])
          -> ([AlterColumn'], [AlterTable])
getAlters :: [EntityDef]
-> EntityDef
-> ([Column], [(DBName, [DBName])])
-> ([Column], [(DBName, [DBName])])
-> ([AlterColumn'], [AlterTable])
getAlters defs :: [EntityDef]
defs def :: EntityDef
def (c1 :: [Column]
c1, u1 :: [(DBName, [DBName])]
u1) (c2 :: [Column]
c2, u2 :: [(DBName, [DBName])]
u2) =
    ([Column] -> [Column] -> [AlterColumn']
getAltersC [Column]
c1 [Column]
c2, [(DBName, [DBName])] -> [(DBName, [DBName])] -> [AlterTable]
getAltersU [(DBName, [DBName])]
u1 [(DBName, [DBName])]
u2)
  where
    getAltersC :: [Column] -> [Column] -> [AlterColumn']
getAltersC [] old :: [Column]
old = (Column -> AlterColumn') -> [Column] -> [AlterColumn']
forall a b. (a -> b) -> [a] -> [b]
map (\x :: Column
x -> (Column -> DBName
cName Column
x, Bool -> AlterColumn
Drop (Bool -> AlterColumn) -> Bool -> AlterColumn
forall a b. (a -> b) -> a -> b
$ EntityDef -> DBName -> Bool
safeToRemove EntityDef
def (DBName -> Bool) -> DBName -> Bool
forall a b. (a -> b) -> a -> b
$ Column -> DBName
cName Column
x)) [Column]
old
    getAltersC (new :: Column
new:news :: [Column]
news) old :: [Column]
old =
        let (alters :: [AlterColumn']
alters, old' :: [Column]
old') = [EntityDef]
-> DBName -> Column -> [Column] -> ([AlterColumn'], [Column])
findAlters [EntityDef]
defs (EntityDef -> DBName
entityDB 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 :: [(DBName, [DBName])]
               -> [(DBName, [DBName])]
               -> [AlterTable]
    getAltersU :: [(DBName, [DBName])] -> [(DBName, [DBName])] -> [AlterTable]
getAltersU [] old :: [(DBName, [DBName])]
old = (DBName -> AlterTable) -> [DBName] -> [AlterTable]
forall a b. (a -> b) -> [a] -> [b]
map DBName -> AlterTable
DropConstraint ([DBName] -> [AlterTable]) -> [DBName] -> [AlterTable]
forall a b. (a -> b) -> a -> b
$ (DBName -> Bool) -> [DBName] -> [DBName]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (DBName -> Bool) -> DBName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DBName -> Bool
isManual) ([DBName] -> [DBName]) -> [DBName] -> [DBName]
forall a b. (a -> b) -> a -> b
$ ((DBName, [DBName]) -> DBName) -> [(DBName, [DBName])] -> [DBName]
forall a b. (a -> b) -> [a] -> [b]
map (DBName, [DBName]) -> DBName
forall a b. (a, b) -> a
fst [(DBName, [DBName])]
old
    getAltersU ((name :: DBName
name, cols :: [DBName]
cols):news :: [(DBName, [DBName])]
news) old :: [(DBName, [DBName])]
old =
        case DBName -> [(DBName, [DBName])] -> Maybe [DBName]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup DBName
name [(DBName, [DBName])]
old of
            Nothing -> DBName -> [DBName] -> AlterTable
AddUniqueConstraint DBName
name [DBName]
cols AlterTable -> [AlterTable] -> [AlterTable]
forall a. a -> [a] -> [a]
: [(DBName, [DBName])] -> [(DBName, [DBName])] -> [AlterTable]
getAltersU [(DBName, [DBName])]
news [(DBName, [DBName])]
old
            Just ocols :: [DBName]
ocols ->
                let old' :: [(DBName, [DBName])]
old' = ((DBName, [DBName]) -> Bool)
-> [(DBName, [DBName])] -> [(DBName, [DBName])]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(x :: DBName
x, _) -> DBName
x DBName -> DBName -> Bool
forall a. Eq a => a -> a -> Bool
/= DBName
name) [(DBName, [DBName])]
old
                 in if [DBName] -> [DBName]
forall a. Ord a => [a] -> [a]
sort [DBName]
cols [DBName] -> [DBName] -> Bool
forall a. Eq a => a -> a -> Bool
== [DBName] -> [DBName]
forall a. Ord a => [a] -> [a]
sort [DBName]
ocols
                        then [(DBName, [DBName])] -> [(DBName, [DBName])] -> [AlterTable]
getAltersU [(DBName, [DBName])]
news [(DBName, [DBName])]
old'
                        else  DBName -> AlterTable
DropConstraint DBName
name
                            AlterTable -> [AlterTable] -> [AlterTable]
forall a. a -> [a] -> [a]
: DBName -> [DBName] -> AlterTable
AddUniqueConstraint DBName
name [DBName]
cols
                            AlterTable -> [AlterTable] -> [AlterTable]
forall a. a -> [a] -> [a]
: [(DBName, [DBName])] -> [(DBName, [DBName])] -> [AlterTable]
getAltersU [(DBName, [DBName])]
news [(DBName, [DBName])]
old'

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

getColumn :: (Text -> IO Statement)
          -> DBName -> [PersistValue]
          -> Maybe (DBName, DBName) 
          -> IO (Either Text Column)
getColumn :: (Text -> IO Statement)
-> DBName
-> [PersistValue]
-> Maybe (DBName, DBName)
-> IO (Either Text Column)
getColumn getter :: Text -> IO Statement
getter tableName' :: DBName
tableName' [PersistText columnName :: Text
columnName, PersistText isNullable :: Text
isNullable, PersistText typeName :: Text
typeName, defaultValue :: PersistValue
defaultValue, numericPrecision :: PersistValue
numericPrecision, numericScale :: PersistValue
numericScale, maxlen :: PersistValue
maxlen] refName :: Maybe (DBName, DBName)
refName =
    case Either Text (Maybe Text)
d' of
        Left s :: Text
s -> 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
s
        Right d'' :: Maybe Text
d'' ->
            let typeStr :: Text
typeStr = case PersistValue
maxlen of
                            PersistInt64 n :: Int64
n -> [Text] -> Text
T.concat [Text
typeName, "(", String -> Text
T.pack (Int64 -> String
forall a. Show a => a -> String
show Int64
n), ")"]
                            _              -> Text
typeName
             in case Text -> Either Text SqlType
getType Text
typeStr of
                  Left s :: Text
s -> 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
s
                  Right t :: SqlType
t -> do
                      let cname :: DBName
cname = Text -> DBName
DBName Text
columnName
                      Maybe (DBName, DBName)
ref <- DBName -> Maybe (DBName, DBName) -> IO (Maybe (DBName, DBName))
getRef DBName
cname Maybe (DBName, DBName)
refName
                      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
$ Column -> Either Text Column
forall a b. b -> Either a b
Right $WColumn :: DBName
-> Bool
-> SqlType
-> Maybe Text
-> Maybe DBName
-> Maybe Integer
-> Maybe (DBName, DBName)
-> Column
Column
                          { cName :: DBName
cName = DBName
cname
                          , cNull :: Bool
cNull = Text
isNullable Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== "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
d''
                          , cDefaultConstraintName :: Maybe DBName
cDefaultConstraintName = Maybe DBName
forall a. Maybe a
Nothing
                          , cMaxLen :: Maybe Integer
cMaxLen = Maybe Integer
forall a. Maybe a
Nothing
                          , cReference :: Maybe (DBName, DBName)
cReference = Maybe (DBName, DBName)
ref
                          }
  where
    stripSuffixes :: Text -> Text
stripSuffixes t :: Text
t =
        [Text] -> Text
loop'
            [ "::character varying"
            , "::text"
            ]
      where
        loop' :: [Text] -> Text
loop' [] = Text
t
        loop' (p :: Text
p:ps :: [Text]
ps) =
            case Text -> Text -> Maybe Text
T.stripSuffix Text
p Text
t of
                Nothing -> [Text] -> Text
loop' [Text]
ps
                Just t' :: Text
t' -> Text
t'
    getRef :: DBName -> Maybe (DBName, DBName) -> IO (Maybe (DBName, DBName))
getRef _ Nothing = Maybe (DBName, DBName) -> IO (Maybe (DBName, DBName))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (DBName, DBName)
forall a. Maybe a
Nothing
    getRef cname :: DBName
cname (Just (_, refName' :: DBName
refName')) = do
        let sql :: Text
sql = [Text] -> Text
T.concat ["SELECT DISTINCT "
                           ,"ccu.table_name, "
                           ,"tc.constraint_name "
                           ,"FROM information_schema.constraint_column_usage ccu, "
                           ,"information_schema.key_column_usage kcu, "
                           ,"information_schema.table_constraints tc "
                           ,"WHERE tc.constraint_type='FOREIGN KEY' "
                           ,"AND kcu.constraint_name=tc.constraint_name "
                           ,"AND ccu.constraint_name=kcu.constraint_name "
                           ,"AND kcu.ordinal_position=1 "
                           ,"AND kcu.table_name=? "
                           ,"AND kcu.column_name=? "
                           ,"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
$ DBName -> Text
unDBName DBName
tableName'
                                      ,Text -> PersistValue
PersistText (Text -> PersistValue) -> Text -> PersistValue
forall a b. (a -> b) -> a -> b
$ DBName -> Text
unDBName DBName
cname
                                      ,Text -> PersistValue
PersistText (Text -> PersistValue) -> Text -> PersistValue
forall a b. (a -> b) -> a -> b
$ DBName -> Text
unDBName DBName
refName'])
                      (\src :: 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 (DBName, DBName) -> IO (Maybe (DBName, DBName))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (DBName, DBName)
forall a. Maybe a
Nothing
          [[PersistText table :: Text
table, PersistText constraint :: Text
constraint]] ->
            Maybe (DBName, DBName) -> IO (Maybe (DBName, DBName))
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (DBName, DBName) -> IO (Maybe (DBName, DBName)))
-> Maybe (DBName, DBName) -> IO (Maybe (DBName, DBName))
forall a b. (a -> b) -> a -> b
$ (DBName, DBName) -> Maybe (DBName, DBName)
forall a. a -> Maybe a
Just (Text -> DBName
DBName Text
table, Text -> DBName
DBName Text
constraint)
          xs :: [[PersistValue]]
xs ->
            String -> IO (Maybe (DBName, DBName))
forall a. HasCallStack => String -> a
error (String -> IO (Maybe (DBName, DBName)))
-> String -> IO (Maybe (DBName, DBName))
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat
              [ "Postgresql.getColumn: error fetching constraints. Expected a single result for foreign key query for table: "
              , Text -> String
T.unpack (DBName -> Text
unDBName DBName
tableName')
              , " and column: "
              , Text -> String
T.unpack (DBName -> Text
unDBName DBName
cname)
              , " but got: "
              , [[PersistValue]] -> String
forall a. Show a => a -> String
show [[PersistValue]]
xs
              ]
    d' :: Either Text (Maybe Text)
d' = case PersistValue
defaultValue of
            PersistNull   -> Maybe Text -> Either Text (Maybe Text)
forall a b. b -> Either a b
Right Maybe Text
forall a. Maybe a
Nothing
            PersistText t :: Text
t -> Maybe Text -> Either Text (Maybe Text)
forall a b. b -> Either a b
Right (Maybe Text -> Either Text (Maybe Text))
-> Maybe Text -> Either Text (Maybe Text)
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t
            _ -> Text -> Either Text (Maybe Text)
forall a b. a -> Either a b
Left (Text -> Either Text (Maybe Text))
-> Text -> Either Text (Maybe Text)
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ "Invalid default column: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ PersistValue -> String
forall a. Show a => a -> String
show PersistValue
defaultValue
    getType :: Text -> Either Text SqlType
getType "int4"        = SqlType -> Either Text SqlType
forall a b. b -> Either a b
Right SqlType
SqlInt32
    getType "int8"        = SqlType -> Either Text SqlType
forall a b. b -> Either a b
Right SqlType
SqlInt64
    getType "varchar"     = SqlType -> Either Text SqlType
forall a b. b -> Either a b
Right SqlType
SqlString
    getType "text"        = SqlType -> Either Text SqlType
forall a b. b -> Either a b
Right SqlType
SqlString
    getType "date"        = SqlType -> Either Text SqlType
forall a b. b -> Either a b
Right SqlType
SqlDay
    getType "bool"        = SqlType -> Either Text SqlType
forall a b. b -> Either a b
Right SqlType
SqlBool
    getType "timestamptz" = SqlType -> Either Text SqlType
forall a b. b -> Either a b
Right SqlType
SqlDayTime
    getType "float4"      = SqlType -> Either Text SqlType
forall a b. b -> Either a b
Right SqlType
SqlReal
    getType "float8"      = SqlType -> Either Text SqlType
forall a b. b -> Either a b
Right SqlType
SqlReal
    getType "bytea"       = SqlType -> Either Text SqlType
forall a b. b -> Either a b
Right SqlType
SqlBlob
    getType "time"        = SqlType -> Either Text SqlType
forall a b. b -> Either a b
Right SqlType
SqlTime
    getType "numeric"     = PersistValue -> PersistValue -> Either Text SqlType
getNumeric PersistValue
numericPrecision PersistValue
numericScale
    getType a :: Text
a             = SqlType -> Either Text SqlType
forall a b. b -> Either a b
Right (SqlType -> Either Text SqlType) -> SqlType -> Either Text SqlType
forall a b. (a -> b) -> a -> b
$ Text -> SqlType
SqlOther Text
a

    getNumeric :: PersistValue -> PersistValue -> Either Text SqlType
getNumeric (PersistInt64 a :: Int64
a) (PersistInt64 b :: Int64
b) = SqlType -> Either Text SqlType
forall a b. b -> Either a b
Right (SqlType -> Either Text SqlType) -> SqlType -> Either Text 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 PersistNull PersistNull = Text -> Either Text SqlType
forall a b. a -> Either a b
Left (Text -> Either Text SqlType) -> Text -> Either Text SqlType
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat
      [ "No precision and scale were specified for the column: "
      , Text
columnName
      , " in table: "
      , DBName -> Text
unDBName DBName
tableName'
      , ". Postgres defaults to a maximum scale of 147,455 and precision of 16383,"
      , " which is probably not what you intended."
      , " Specify the values as numeric(total_digits, digits_after_decimal_place)."
      ]
    getNumeric a :: PersistValue
a b :: PersistValue
b = Text -> Either Text SqlType
forall a b. a -> Either a b
Left (Text -> Either Text SqlType) -> Text -> Either Text SqlType
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat
      [ "Can not get numeric field precision for the column: "
      , Text
columnName
      , " in table: "
      , DBName -> Text
unDBName DBName
tableName'
      , ". Expected an integer for both precision and scale, "
      , "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
      , " 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
      , ", respectively."
      , " Specify the values as numeric(total_digits, digits_after_decimal_place)."
      ]
getColumn _ _ columnName :: [PersistValue]
columnName _ =
    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
$ "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 x :: SqlType
x y :: 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] -> DBName -> Column -> [Column] -> ([AlterColumn'], [Column])
findAlters :: [EntityDef]
-> DBName -> Column -> [Column] -> ([AlterColumn'], [Column])
findAlters defs :: [EntityDef]
defs _tablename :: DBName
_tablename col :: Column
col@(Column name :: DBName
name isNull :: Bool
isNull sqltype :: SqlType
sqltype def :: Maybe Text
def _defConstraintName :: Maybe DBName
_defConstraintName _maxLen :: Maybe Integer
_maxLen ref :: Maybe (DBName, DBName)
ref) cols :: [Column]
cols =
    case (Column -> Bool) -> [Column] -> [Column]
forall a. (a -> Bool) -> [a] -> [a]
filter (\c :: Column
c -> Column -> DBName
cName Column
c DBName -> DBName -> Bool
forall a. Eq a => a -> a -> Bool
== DBName
name) [Column]
cols of
        [] -> ([(DBName
name, Column -> AlterColumn
Add' Column
col)], [Column]
cols)
        Column _ isNull' :: Bool
isNull' sqltype' :: SqlType
sqltype' def' :: Maybe Text
def' _defConstraintName' :: Maybe DBName
_defConstraintName' _maxLen' :: Maybe Integer
_maxLen' ref' :: Maybe (DBName, DBName)
ref':_ ->
            let refDrop :: Maybe (DBName, DBName) -> [AlterColumn']
refDrop Nothing = []
                refDrop (Just (_, cname :: DBName
cname)) = [(DBName
name, DBName -> AlterColumn
DropReference DBName
cname)]
                refAdd :: Maybe (DBName, DBName) -> [AlterColumn']
refAdd Nothing = []
                refAdd (Just (tname :: DBName
tname, a :: DBName
a)) =
                    case (EntityDef -> Bool) -> [EntityDef] -> Maybe EntityDef
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((DBName -> DBName -> Bool
forall a. Eq a => a -> a -> Bool
==DBName
tname) (DBName -> Bool) -> (EntityDef -> DBName) -> EntityDef -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntityDef -> DBName
entityDB) [EntityDef]
defs of
                        Just refdef :: EntityDef
refdef -> [(DBName
tname, DBName -> [DBName] -> [Text] -> AlterColumn
AddReference DBName
a [DBName
name] ((DBName -> Text) -> EntityDef -> [Text]
Util.dbIdColumnsEsc DBName -> Text
escape EntityDef
refdef))]
                        Nothing -> String -> [AlterColumn']
forall a. HasCallStack => String -> a
error (String -> [AlterColumn']) -> String -> [AlterColumn']
forall a b. (a -> b) -> a -> b
$ "could not find the entityDef for reftable[" String -> ShowS
forall a. [a] -> [a] -> [a]
++ DBName -> String
forall a. Show a => a -> String
show DBName
tname String -> ShowS
forall a. [a] -> [a] -> [a]
++ "]"
                modRef :: [AlterColumn']
modRef =
                    if ((DBName, DBName) -> DBName)
-> Maybe (DBName, DBName) -> Maybe DBName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (DBName, DBName) -> DBName
forall a b. (a, b) -> b
snd Maybe (DBName, DBName)
ref Maybe DBName -> Maybe DBName -> Bool
forall a. Eq a => a -> a -> Bool
== ((DBName, DBName) -> DBName)
-> Maybe (DBName, DBName) -> Maybe DBName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (DBName, DBName) -> DBName
forall a b. (a, b) -> b
snd Maybe (DBName, DBName)
ref'
                        then []
                        else Maybe (DBName, DBName) -> [AlterColumn']
refDrop Maybe (DBName, DBName)
ref' [AlterColumn'] -> [AlterColumn'] -> [AlterColumn']
forall a. [a] -> [a] -> [a]
++ Maybe (DBName, DBName) -> [AlterColumn']
refAdd Maybe (DBName, DBName)
ref
                modNull :: [AlterColumn']
modNull = case (Bool
isNull, Bool
isNull') of
                            (True, False) -> [(DBName
name, AlterColumn
IsNull)]
                            (False, True) ->
                                let up :: [AlterColumn'] -> [AlterColumn']
up = case Maybe Text
def of
                                            Nothing -> [AlterColumn'] -> [AlterColumn']
forall a. a -> a
id
                                            Just s :: Text
s -> (:) (DBName
name, Text -> AlterColumn
Update' Text
s)
                                 in [AlterColumn'] -> [AlterColumn']
up [(DBName
name, AlterColumn
NotNull)]
                            _ -> []
                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 "timestamp" =
                        [(DBName
name, SqlType -> Text -> AlterColumn
ChangeType SqlType
sqltype (Text -> AlterColumn) -> Text -> AlterColumn
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat
                            [ " USING "
                            , DBName -> Text
escape DBName
name
                            , " AT TIME ZONE 'UTC'"
                            ])]
                    | Bool
otherwise = [(DBName
name, SqlType -> Text -> AlterColumn
ChangeType SqlType
sqltype "")]
                modDef :: [AlterColumn']
modDef =
                    if Maybe Text
def Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe Text
def'
                        then []
                        else case Maybe Text
def of
                                Nothing -> [(DBName
name, AlterColumn
NoDefault)]
                                Just s :: Text
s -> [(DBName
name, Text -> AlterColumn
Default Text
s)]
             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,
                 (Column -> Bool) -> [Column] -> [Column]
forall a. (a -> Bool) -> [a] -> [a]
filter (\c :: Column
c -> Column -> DBName
cName Column
c DBName -> DBName -> Bool
forall a. Eq a => a -> a -> Bool
/= DBName
name) [Column]
cols)

-- | Get the references to be added to a table for the given column.
getAddReference :: [EntityDef] -> DBName -> DBName -> DBName -> Maybe (DBName, DBName) -> Maybe AlterDB
getAddReference :: [EntityDef]
-> DBName
-> DBName
-> DBName
-> Maybe (DBName, DBName)
-> Maybe AlterDB
getAddReference allDefs :: [EntityDef]
allDefs table :: DBName
table reftable :: DBName
reftable cname :: DBName
cname ref :: Maybe (DBName, DBName)
ref =
    case Maybe (DBName, DBName)
ref of
        Nothing -> Maybe AlterDB
forall a. Maybe a
Nothing
        Just (s :: DBName
s, constraintName :: DBName
constraintName) -> AlterDB -> Maybe AlterDB
forall a. a -> Maybe a
Just (AlterDB -> Maybe AlterDB) -> AlterDB -> Maybe AlterDB
forall a b. (a -> b) -> a -> b
$ DBName -> AlterColumn' -> AlterDB
AlterColumn DBName
table (DBName
s, DBName -> [DBName] -> [Text] -> AlterColumn
AddReference DBName
constraintName [DBName
cname] [Text]
id_)
                          where
                            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
$ "Could not find ID of entity " String -> ShowS
forall a. [a] -> [a] -> [a]
++ DBName -> String
forall a. Show a => a -> String
show DBName
reftable)
                                        (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 ((DBName -> DBName -> Bool
forall a. Eq a => a -> a -> Bool
== DBName
reftable) (DBName -> Bool) -> (EntityDef -> DBName) -> EntityDef -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntityDef -> DBName
entityDB) [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
$ (DBName -> Text) -> EntityDef -> [Text]
Util.dbIdColumnsEsc DBName -> Text
escape EntityDef
entDef


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

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

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

showSqlType (SqlOther t :: Text
t) = Text
t

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

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

showAlter :: DBName -> AlterColumn' -> Text
showAlter :: DBName -> AlterColumn' -> Text
showAlter table :: DBName
table (n :: DBName
n, ChangeType t :: SqlType
t extra :: Text
extra) =
    [Text] -> Text
T.concat
        [ "ALTER TABLE "
        , DBName -> Text
escape DBName
table
        , " ALTER COLUMN "
        , DBName -> Text
escape DBName
n
        , " TYPE "
        , SqlType -> Text
showSqlType SqlType
t
        , Text
extra
        ]
showAlter table :: DBName
table (n :: DBName
n, IsNull) =
    [Text] -> Text
T.concat
        [ "ALTER TABLE "
        , DBName -> Text
escape DBName
table
        , " ALTER COLUMN "
        , DBName -> Text
escape DBName
n
        , " DROP NOT NULL"
        ]
showAlter table :: DBName
table (n :: DBName
n, NotNull) =
    [Text] -> Text
T.concat
        [ "ALTER TABLE "
        , DBName -> Text
escape DBName
table
        , " ALTER COLUMN "
        , DBName -> Text
escape DBName
n
        , " SET NOT NULL"
        ]
showAlter table :: DBName
table (_, Add' col :: Column
col) =
    [Text] -> Text
T.concat
        [ "ALTER TABLE "
        , DBName -> Text
escape DBName
table
        , " ADD COLUMN "
        , Column -> Text
showColumn Column
col
        ]
showAlter table :: DBName
table (n :: DBName
n, Drop _) =
    [Text] -> Text
T.concat
        [ "ALTER TABLE "
        , DBName -> Text
escape DBName
table
        , " DROP COLUMN "
        , DBName -> Text
escape DBName
n
        ]
showAlter table :: DBName
table (n :: DBName
n, Default s :: Text
s) =
    [Text] -> Text
T.concat
        [ "ALTER TABLE "
        , DBName -> Text
escape DBName
table
        , " ALTER COLUMN "
        , DBName -> Text
escape DBName
n
        , " SET DEFAULT "
        , Text
s
        ]
showAlter table :: DBName
table (n :: DBName
n, NoDefault) = [Text] -> Text
T.concat
    [ "ALTER TABLE "
    , DBName -> Text
escape DBName
table
    , " ALTER COLUMN "
    , DBName -> Text
escape DBName
n
    , " DROP DEFAULT"
    ]
showAlter table :: DBName
table (n :: DBName
n, Update' s :: Text
s) = [Text] -> Text
T.concat
    [ "UPDATE "
    , DBName -> Text
escape DBName
table
    , " SET "
    , DBName -> Text
escape DBName
n
    , "="
    , Text
s
    , " WHERE "
    , DBName -> Text
escape DBName
n
    , " IS NULL"
    ]
showAlter table :: DBName
table (reftable :: DBName
reftable, AddReference fkeyname :: DBName
fkeyname t2 :: [DBName]
t2 id2 :: [Text]
id2) = [Text] -> Text
T.concat
    [ "ALTER TABLE "
    , DBName -> Text
escape DBName
table
    , " ADD CONSTRAINT "
    , DBName -> Text
escape DBName
fkeyname
    , " FOREIGN KEY("
    , Text -> [Text] -> Text
T.intercalate "," ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (DBName -> Text) -> [DBName] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map DBName -> Text
escape [DBName]
t2
    , ") REFERENCES "
    , DBName -> Text
escape DBName
reftable
    , "("
    , Text -> [Text] -> Text
T.intercalate "," [Text]
id2
    , ")"
    ]
showAlter table :: DBName
table (_, DropReference cname :: DBName
cname) = [Text] -> Text
T.concat
    [ "ALTER TABLE "
    , DBName -> Text
escape DBName
table
    , " DROP CONSTRAINT "
    , DBName -> Text
escape DBName
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 = DBName -> Text
escape (DBName -> Text) -> (record -> DBName) -> record -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. record -> DBName
forall record. PersistEntity record => record -> DBName
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 = DBName -> Text
escape (DBName -> Text)
-> (EntityField record typ -> DBName)
-> EntityField record typ
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntityField record typ -> DBName
forall record typ.
PersistEntity record =>
EntityField record typ -> DBName
fieldDBName

escape :: DBName -> Text
escape :: DBName -> Text
escape (DBName s :: Text
s) =
    String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ '"' Char -> ShowS
forall a. a -> [a] -> [a]
: ShowS
go (Text -> String
T.unpack Text
s) String -> ShowS
forall a. [a] -> [a] -> [a]
++ "\""
  where
    go :: ShowS
go "" = ""
    go ('"':xs :: String
xs) = "\"\"" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
go String
xs
    go (x :: Char
x:xs :: 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.
    , 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
Constr
DataType
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 -> Constr
PostgresConf -> DataType
(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, Typeable)

instance FromJSON PostgresConf where
    parseJSON :: Value -> Parser PostgresConf
parseJSON v :: Value
v = ShowS -> Parser PostgresConf -> Parser PostgresConf
forall a. ShowS -> Parser a -> Parser a
modifyFailure ("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 "PostgresConf") Value
v ((Object -> Parser PostgresConf) -> Parser PostgresConf)
-> (Object -> Parser PostgresConf) -> Parser PostgresConf
forall a b. (a -> b) -> a -> b
$ \o :: Object
o -> do
        String
database <- Object
o Object -> Text -> Parser String
forall a. FromJSON a => Object -> Text -> Parser a
.: "database"
        String
host     <- Object
o Object -> Text -> Parser String
forall a. FromJSON a => Object -> Text -> Parser a
.: "host"
        Word16
port     <- Object
o Object -> Text -> Parser (Maybe Word16)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? "port" Parser (Maybe Word16) -> Word16 -> Parser Word16
forall a. Parser (Maybe a) -> a -> Parser a
.!= 5432
        String
user     <- Object
o Object -> Text -> Parser String
forall a. FromJSON a => Object -> Text -> Parser a
.: "user"
        String
password <- Object
o Object -> Text -> Parser String
forall a. FromJSON a => Object -> Text -> Parser a
.: "password"
        Int
pool     <- Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: "poolsize"
        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 -> PostgresConf
PostgresConf ConnectionString
cstr Int
pool
instance PersistConfig PostgresConf where
    type PersistConfigBackend PostgresConf = SqlPersistT
    type PersistConfigPool PostgresConf = ConnectionPool
    createPoolConfig :: PostgresConf -> IO (PersistConfigPool PostgresConf)
createPoolConfig (PostgresConf cs :: ConnectionString
cs size :: Int
size) = NoLoggingT IO (Pool SqlBackend)
-> IO (PersistConfigPool PostgresConf)
forall (m :: * -> *) a. NoLoggingT m a -> m a
runNoLoggingT (NoLoggingT IO (Pool SqlBackend)
 -> IO (PersistConfigPool PostgresConf))
-> NoLoggingT IO (Pool SqlBackend)
-> IO (PersistConfigPool PostgresConf)
forall a b. (a -> b) -> a -> b
$ ConnectionString -> Int -> NoLoggingT IO (Pool SqlBackend)
forall (m :: * -> *).
(MonadUnliftIO m, MonadLogger m) =>
ConnectionString -> Int -> m (Pool SqlBackend)
createPostgresqlPool ConnectionString
cs Int
size -- FIXME
    runPool :: PostgresConf
-> PersistConfigBackend PostgresConf m a
-> PersistConfigPool PostgresConf
-> m a
runPool _ = PersistConfigBackend PostgresConf m a
-> PersistConfigPool PostgresConf -> m a
forall (m :: * -> *) backend 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 c0 :: 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 param :: ConnectionString
param val :: String
val c :: PostgresConf
c =
            PostgresConf
c { pgConnStr :: ConnectionString
pgConnStr = [ConnectionString] -> ConnectionString
B8.concat [PostgresConf -> ConnectionString
pgConnStr PostgresConf
c, " ", ConnectionString
param, "='", String -> ConnectionString
pgescape String
val, "'"] }

        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 ('\'':rest :: String
rest) = '\\' Char -> ShowS
forall a. a -> [a] -> [a]
: '\'' Char -> ShowS
forall a. a -> [a] -> [a]
: ShowS
go String
rest
              go ('\\':rest :: String
rest) = '\\' Char -> ShowS
forall a. a -> [a] -> [a]
: '\\' Char -> ShowS
forall a. a -> [a] -> [a]
: ShowS
go String
rest
              go ( x :: Char
x  :rest :: String
rest) =      Char
x      Char -> ShowS
forall a. a -> [a] -> [a]
: ShowS
go String
rest
              go []          = []

        maybeAddParam :: ConnectionString
-> a -> [(a, String)] -> PostgresConf -> PostgresConf
maybeAddParam param :: ConnectionString
param envvar :: a
envvar env :: [(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 "host"     "PGHOST"
        addPort :: [(String, String)] -> PostgresConf -> PostgresConf
addPort     = ConnectionString
-> String -> [(String, String)] -> PostgresConf -> PostgresConf
forall a.
Eq a =>
ConnectionString
-> a -> [(a, String)] -> PostgresConf -> PostgresConf
maybeAddParam "port"     "PGPORT"
        addUser :: [(String, String)] -> PostgresConf -> PostgresConf
addUser     = ConnectionString
-> String -> [(String, String)] -> PostgresConf -> PostgresConf
forall a.
Eq a =>
ConnectionString
-> a -> [(a, String)] -> PostgresConf -> PostgresConf
maybeAddParam "user"     "PGUSER"
        addPass :: [(String, String)] -> PostgresConf -> PostgresConf
addPass     = ConnectionString
-> String -> [(String, String)] -> PostgresConf -> PostgresConf
forall a.
Eq a =>
ConnectionString
-> a -> [(a, String)] -> PostgresConf -> PostgresConf
maybeAddParam "password" "PGPASS"
        addDatabase :: [(String, String)] -> PostgresConf -> PostgresConf
addDatabase = ConnectionString
-> String -> [(String, String)] -> PostgresConf -> PostgresConf
forall a.
Eq a =>
ConnectionString
-> a -> [(a, String)] -> PostgresConf -> PostgresConf
maybeAddParam "dbname"   "PGDATABASE"

udToPair :: UniqueDef -> (DBName, [DBName])
udToPair :: UniqueDef -> (DBName, [DBName])
udToPair ud :: UniqueDef
ud = (UniqueDef -> DBName
uniqueDBName UniqueDef
ud, ((HaskellName, DBName) -> DBName)
-> [(HaskellName, DBName)] -> [DBName]
forall a b. (a -> b) -> [a] -> [b]
map (HaskellName, DBName) -> DBName
forall a b. (a, b) -> b
snd ([(HaskellName, DBName)] -> [DBName])
-> [(HaskellName, DBName)] -> [DBName]
forall a b. (a -> b) -> a -> b
$ UniqueDef -> [(HaskellName, DBName)]
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 allDefs :: [EntityDef]
allDefs _ entity :: 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 (DBName, [DBName]))]
-> ([Text], [Either Column (DBName, [DBName])])
forall a b. [Either a b] -> ([a], [b])
partitionEithers [] of
        ([], old'' :: [Either Column (DBName, [DBName])]
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 (DBName, [DBName])] -> [AlterDB]
migrationText Bool
False [Either Column (DBName, [DBName])]
old''
        (errs :: [Text]
errs, _) -> 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 :: DBName
name = EntityDef -> DBName
entityDB EntityDef
entity
    migrationText :: Bool -> [Either Column (DBName, [DBName])] -> [AlterDB]
migrationText exists :: Bool
exists old'' :: [Either Column (DBName, [DBName])]
old'' =
        if Bool -> Bool
not Bool
exists
            then [Column] -> [ForeignDef] -> [(DBName, [DBName])] -> [AlterDB]
createText [Column]
newcols [ForeignDef]
fdefs [(DBName, [DBName])]
udspair
            else let (acs :: [AlterColumn']
acs, ats :: [AlterTable]
ats) = [EntityDef]
-> EntityDef
-> ([Column], [(DBName, [DBName])])
-> ([Column], [(DBName, [DBName])])
-> ([AlterColumn'], [AlterTable])
getAlters [EntityDef]
allDefs EntityDef
entity ([Column]
newcols, [(DBName, [DBName])]
udspair) ([Column], [(DBName, [DBName])])
old'
                     acs' :: [AlterDB]
acs' = (AlterColumn' -> AlterDB) -> [AlterColumn'] -> [AlterDB]
forall a b. (a -> b) -> [a] -> [b]
map (DBName -> AlterColumn' -> AlterDB
AlterColumn DBName
name) [AlterColumn']
acs
                     ats' :: [AlterDB]
ats' = (AlterTable -> AlterDB) -> [AlterTable] -> [AlterDB]
forall a b. (a -> b) -> [a] -> [b]
map (DBName -> AlterTable -> AlterDB
AlterTable DBName
name) [AlterTable]
ats
                 in  [AlterDB]
acs' [AlterDB] -> [AlterDB] -> [AlterDB]
forall a. [a] -> [a] -> [a]
++ [AlterDB]
ats'
       where
         old' :: ([Column], [(DBName, [DBName])])
old' = [Either Column (DBName, [DBName])]
-> ([Column], [(DBName, [DBName])])
forall a b. [Either a b] -> ([a], [b])
partitionEithers [Either Column (DBName, [DBName])]
old''
         (newcols' :: [Column]
newcols', udefs :: [UniqueDef]
udefs, fdefs :: [ForeignDef]
fdefs) = [EntityDef] -> EntityDef -> ([Column], [UniqueDef], [ForeignDef])
mkColumns [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 -> DBName -> Bool
safeToRemove EntityDef
entity (DBName -> Bool) -> (Column -> DBName) -> Column -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Column -> DBName
cName) [Column]
newcols'
         udspair :: [(DBName, [DBName])]
udspair = (UniqueDef -> (DBName, [DBName]))
-> [UniqueDef] -> [(DBName, [DBName])]
forall a b. (a -> b) -> [a] -> [b]
map UniqueDef -> (DBName, [DBName])
udToPair [UniqueDef]
udefs
            -- Check for table existence if there are no columns, workaround
            -- for https://github.com/yesodweb/persistent/issues/152

    createText :: [Column] -> [ForeignDef] -> [(DBName, [DBName])] -> [AlterDB]
createText newcols :: [Column]
newcols fdefs :: [ForeignDef]
fdefs udspair :: [(DBName, [DBName])]
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 = (((DBName, [DBName]) -> [AlterDB])
 -> [(DBName, [DBName])] -> [AlterDB])
-> [(DBName, [DBName])]
-> ((DBName, [DBName]) -> [AlterDB])
-> [AlterDB]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((DBName, [DBName]) -> [AlterDB])
-> [(DBName, [DBName])] -> [AlterDB]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap [(DBName, [DBName])]
udspair (((DBName, [DBName]) -> [AlterDB]) -> [AlterDB])
-> ((DBName, [DBName]) -> [AlterDB]) -> [AlterDB]
forall a b. (a -> b) -> a -> b
$ \(uname :: DBName
uname, ucols :: [DBName]
ucols) ->
                [DBName -> AlterTable -> AlterDB
AlterTable DBName
name (AlterTable -> AlterDB) -> AlterTable -> AlterDB
forall a b. (a -> b) -> a -> b
$ DBName -> [DBName] -> AlterTable
AddUniqueConstraint DBName
uname [DBName]
ucols]
        references :: [AlterDB]
references = (Column -> Maybe AlterDB) -> [Column] -> [AlterDB]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (\c :: Column
c@Column { cName :: Column -> DBName
cName=DBName
cname, cReference :: Column -> Maybe (DBName, DBName)
cReference=Just (refTblName :: DBName
refTblName, _) } ->
            [EntityDef]
-> DBName
-> DBName
-> DBName
-> Maybe (DBName, DBName)
-> Maybe AlterDB
getAddReference [EntityDef]
allDefs DBName
name DBName
refTblName DBName
cname (Column -> Maybe (DBName, DBName)
cReference Column
c))
                   ([Column] -> [AlterDB]) -> [Column] -> [AlterDB]
forall a b. (a -> b) -> a -> b
$ (Column -> Bool) -> [Column] -> [Column]
forall a. (a -> Bool) -> [a] -> [a]
filter (Maybe (DBName, DBName) -> Bool
forall a. Maybe a -> Bool
isJust (Maybe (DBName, DBName) -> Bool)
-> (Column -> Maybe (DBName, DBName)) -> Column -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Column -> Maybe (DBName, DBName)
cReference) [Column]
newcols
        foreignsAlt :: [AlterDB]
foreignsAlt = ((ForeignDef -> AlterDB) -> [ForeignDef] -> [AlterDB])
-> [ForeignDef] -> (ForeignDef -> AlterDB) -> [AlterDB]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (ForeignDef -> AlterDB) -> [ForeignDef] -> [AlterDB]
forall a b. (a -> b) -> [a] -> [b]
map [ForeignDef]
fdefs (\fdef :: ForeignDef
fdef ->
            let (childfields :: [DBName]
childfields, parentfields :: [DBName]
parentfields) = [(DBName, DBName)] -> ([DBName], [DBName])
forall a b. [(a, b)] -> ([a], [b])
unzip ((((HaskellName, DBName), (HaskellName, DBName))
 -> (DBName, DBName))
-> [((HaskellName, DBName), (HaskellName, DBName))]
-> [(DBName, DBName)]
forall a b. (a -> b) -> [a] -> [b]
map (\((_,b :: DBName
b),(_,d :: DBName
d)) -> (DBName
b,DBName
d)) (ForeignDef -> [((HaskellName, DBName), (HaskellName, DBName))]
foreignFields ForeignDef
fdef))
            in DBName -> AlterColumn' -> AlterDB
AlterColumn DBName
name (ForeignDef -> DBName
foreignRefTableDBName ForeignDef
fdef, DBName -> [DBName] -> [Text] -> AlterColumn
AddReference (ForeignDef -> DBName
foreignConstraintNameDBName ForeignDef
fdef) [DBName]
childfields ((DBName -> Text) -> [DBName] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map DBName -> Text
escape [DBName]
parentfields)))

-- | 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 mig :: 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 -> IO (IORef (Map Text Statement)))
-> Map Text Statement -> IO (IORef (Map Text Statement))
forall a b. (a -> b) -> a -> b
$ Map Text Statement
forall k a. Map k a
Map.empty
  let sqlbackend :: SqlBackend
sqlbackend = SqlBackend :: (Text -> IO Statement)
-> (EntityDef -> [PersistValue] -> InsertSqlResult)
-> Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
-> Maybe (EntityDef -> NonEmpty UniqueDef -> Text -> Text)
-> Maybe (EntityDef -> Int -> Text)
-> 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 ())
-> (DBName -> Text)
-> Text
-> Text
-> ((Int, Int) -> Bool -> Text -> Text)
-> LogFunc
-> Maybe Int
-> Maybe (EntityDef -> Int -> Text)
-> SqlBackend
SqlBackend { connPrepare :: Text -> IO Statement
connPrepare = \_ -> 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 = \_ -> ConduitT () [PersistValue] m ()
-> Acquire (ConduitT () [PersistValue] m ())
forall (m :: * -> *) a. Monad m => a -> m a
return (ConduitT () [PersistValue] m ()
 -> Acquire (ConduitT () [PersistValue] m ()))
-> ConduitT () [PersistValue] m ()
-> Acquire (ConduitT () [PersistValue] m ())
forall a b. (a -> b) -> a -> b
$ () -> ConduitT () [PersistValue] m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
                                                        },
                             connInsertManySql :: Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
connInsertManySql = Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
forall a. Maybe a
Nothing,
                             connInsertSql :: EntityDef -> [PersistValue] -> InsertSqlResult
connInsertSql = EntityDef -> [PersistValue] -> InsertSqlResult
forall a. HasCallStack => a
undefined,
                             connUpsertSql :: Maybe (EntityDef -> NonEmpty UniqueDef -> Text -> Text)
connUpsertSql = Maybe (EntityDef -> NonEmpty UniqueDef -> Text -> Text)
forall a. Maybe a
Nothing,
                             connPutManySql :: Maybe (EntityDef -> Int -> Text)
connPutManySql = Maybe (EntityDef -> Int -> Text)
forall a. Maybe a
Nothing,
                             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,
                             connEscapeName :: DBName -> Text
connEscapeName = DBName -> Text
escape,
                             connNoLimit :: Text
connNoLimit = Text
forall a. HasCallStack => a
undefined,
                             connRDBMS :: Text
connRDBMS = Text
forall a. HasCallStack => a
undefined,
                             connLimitOffset :: (Int, Int) -> Bool -> Text -> Text
connLimitOffset = (Int, Int) -> Bool -> Text -> Text
forall a. HasCallStack => a
undefined,
                             connLogFunc :: LogFunc
connLogFunc = LogFunc
forall a. HasCallStack => a
undefined,
                             connMaxParams :: Maybe Int
connMaxParams = Maybe Int
forall a. Maybe a
Nothing,
                             connRepsertManySql :: Maybe (EntityDef -> Int -> Text)
connRepsertManySql = Maybe (EntityDef -> Int -> Text)
forall a. Maybe a
Nothing
                             }
      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 ent :: EntityDef
ent n :: Int
n = [Text] -> [FieldDef] -> EntityDef -> Int -> Text
putManySql' [Text]
conflictColumns [FieldDef]
fields EntityDef
ent Int
n
  where
    fields :: [FieldDef]
fields = EntityDef -> [FieldDef]
entityFields EntityDef
ent
    conflictColumns :: [Text]
conflictColumns = (UniqueDef -> [Text]) -> [UniqueDef] -> [Text]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (((HaskellName, DBName) -> Text)
-> [(HaskellName, DBName)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (DBName -> Text
escape (DBName -> Text)
-> ((HaskellName, DBName) -> DBName)
-> (HaskellName, DBName)
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HaskellName, DBName) -> DBName
forall a b. (a, b) -> b
snd) ([(HaskellName, DBName)] -> [Text])
-> (UniqueDef -> [(HaskellName, DBName)]) -> UniqueDef -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UniqueDef -> [(HaskellName, DBName)]
uniqueFields) (EntityDef -> [UniqueDef]
entityUniques EntityDef
ent)

repsertManySql :: EntityDef -> Int -> Text
repsertManySql :: EntityDef -> Int -> Text
repsertManySql ent :: EntityDef
ent n :: Int
n = [Text] -> [FieldDef] -> EntityDef -> Int -> Text
putManySql' [Text]
conflictColumns [FieldDef]
fields EntityDef
ent Int
n
  where
    fields :: [FieldDef]
fields = EntityDef -> [FieldDef]
keyAndEntityFields EntityDef
ent
    conflictColumns :: [Text]
conflictColumns = DBName -> Text
escape (DBName -> Text) -> (FieldDef -> DBName) -> FieldDef -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldDef -> DBName
fieldDB (FieldDef -> Text) -> [FieldDef] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> EntityDef -> [FieldDef]
entityKeyFields EntityDef
ent

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

    table :: Text
table = DBName -> Text
escape (DBName -> Text) -> (EntityDef -> DBName) -> EntityDef -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntityDef -> DBName
entityDB (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 "?") [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
        [ "INSERT INTO "
        , Text
table
        , Text -> Text
Util.parenWrapped Text
columns
        , " 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
        , " 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
        , " 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 extName :: 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 "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 0]
    then (((), [Text]), [(Bool, Text)])
-> ReaderT SqlBackend IO (((), [Text]), [(Bool, Text)])
forall (m :: * -> *) a. Monad m => a -> m a
return (((), []) , [(Bool
False, "CREATe EXTENSION \"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
extName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> "\"")])
    else (((), [Text]), [(Bool, Text)])
-> ReaderT SqlBackend IO (((), [Text]), [(Bool, Text)])
forall (m :: * -> *) a. Monad m => a -> m a
return (((), []), [])