module Database.Persist.SqlBackend
    ( 
      SqlBackend
    , mkSqlBackend
    , MkSqlBackendArgs(..)
    , SqlBackendHooks
    , emptySqlBackendHooks
    
    
    
    , getRDBMS
    , getEscapedFieldName
    , getEscapedRawName
    , getEscapeRawNameFunction
    , getConnLimitOffset
    , getConnUpsertSql
    , getConnVault
    , getConnHooks
    
    , setConnMaxParams
    , setConnRepsertManySql
    , setConnInsertManySql
    , setConnUpsertSql
    , setConnPutManySql
    , setConnVault
    , modifyConnVault
    , setConnHooks
    
    ) where
import Control.Monad.Reader
import Data.List.NonEmpty (NonEmpty)
import Data.Text (Text)
import Data.Vault.Strict (Vault)
import Database.Persist.Class.PersistStore (BackendCompatible(..))
import Database.Persist.Names
import Database.Persist.SqlBackend.Internal
import qualified Database.Persist.SqlBackend.Internal as SqlBackend
       (SqlBackend(..))
import Database.Persist.SqlBackend.Internal.InsertSqlResult
import Database.Persist.SqlBackend.Internal.MkSqlBackend as Mk
       (MkSqlBackendArgs(..))
import Database.Persist.Types.Base
getEscapedFieldName
    :: (BackendCompatible SqlBackend backend, MonadReader backend m)
    => FieldNameDB -> m Text
getEscapedFieldName :: forall backend (m :: * -> *).
(BackendCompatible SqlBackend backend, MonadReader backend m) =>
FieldNameDB -> m Text
getEscapedFieldName FieldNameDB
fieldName = do
    FieldNameDB -> Text
func <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (SqlBackend -> FieldNameDB -> Text
SqlBackend.connEscapeFieldName forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall sup sub. BackendCompatible sup sub => sub -> sup
projectBackend)
    forall (f :: * -> *) a. Applicative f => a -> f a
pure (FieldNameDB -> Text
func FieldNameDB
fieldName)
getEscapedRawName
    :: (BackendCompatible SqlBackend backend, MonadReader backend m)
    => Text -> m Text
getEscapedRawName :: forall backend (m :: * -> *).
(BackendCompatible SqlBackend backend, MonadReader backend m) =>
Text -> m Text
getEscapedRawName Text
name = do
    Text -> Text
func <- forall backend (m :: * -> *).
(BackendCompatible SqlBackend backend, MonadReader backend m) =>
m (Text -> Text)
getEscapeRawNameFunction
    forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Text
func Text
name)
getEscapeRawNameFunction
    :: (BackendCompatible SqlBackend backend, MonadReader backend m)
    => m (Text -> Text)
getEscapeRawNameFunction :: forall backend (m :: * -> *).
(BackendCompatible SqlBackend backend, MonadReader backend m) =>
m (Text -> Text)
getEscapeRawNameFunction = do
    forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (SqlBackend -> Text -> Text
SqlBackend.connEscapeRawName forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall sup sub. BackendCompatible sup sub => sub -> sup
projectBackend)
getConnLimitOffset
    :: (BackendCompatible SqlBackend backend, MonadReader backend m)
    => (Int, Int)
    
    -> Text
    
    -> m Text
getConnLimitOffset :: forall backend (m :: * -> *).
(BackendCompatible SqlBackend backend, MonadReader backend m) =>
(Int, Int) -> Text -> m Text
getConnLimitOffset (Int, Int)
limitOffset Text
sql = do
    (Int, Int) -> Text -> Text
func <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (SqlBackend -> (Int, Int) -> Text -> Text
SqlBackend.connLimitOffset forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall sup sub. BackendCompatible sup sub => sub -> sup
projectBackend)
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (Int, Int) -> Text -> Text
func (Int, Int)
limitOffset Text
sql
getConnUpsertSql
    :: (BackendCompatible SqlBackend backend, MonadReader backend m)
    => m (Maybe (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text))
getConnUpsertSql :: forall backend (m :: * -> *).
(BackendCompatible SqlBackend backend, MonadReader backend m) =>
m (Maybe
     (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text))
getConnUpsertSql = do
    forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (SqlBackend
-> Maybe
     (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)
SqlBackend.connUpsertSql forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall sup sub. BackendCompatible sup sub => sub -> sup
projectBackend)
getConnVault
    ::  (BackendCompatible SqlBackend backend, MonadReader backend m)
    => m Vault
getConnVault :: forall backend (m :: * -> *).
(BackendCompatible SqlBackend backend, MonadReader backend m) =>
m Vault
getConnVault = do
    forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (SqlBackend -> Vault
SqlBackend.connVault forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall sup sub. BackendCompatible sup sub => sub -> sup
projectBackend)
getConnHooks
    ::  (BackendCompatible SqlBackend backend, MonadReader backend m)
    => m SqlBackendHooks
getConnHooks :: forall backend (m :: * -> *).
(BackendCompatible SqlBackend backend, MonadReader backend m) =>
m SqlBackendHooks
getConnHooks = do
    forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (SqlBackend -> SqlBackendHooks
SqlBackend.connHooks forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall sup sub. BackendCompatible sup sub => sub -> sup
projectBackend)
getRDBMS
    :: (BackendCompatible SqlBackend backend, MonadReader backend m)
    => m Text
getRDBMS :: forall backend (m :: * -> *).
(BackendCompatible SqlBackend backend, MonadReader backend m) =>
m Text
getRDBMS = do
    forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (SqlBackend -> Text
SqlBackend.connRDBMS forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall sup sub. BackendCompatible sup sub => sub -> sup
projectBackend)
setConnMaxParams
    :: Int
    -> SqlBackend
    -> SqlBackend
setConnMaxParams :: Int -> SqlBackend -> SqlBackend
setConnMaxParams Int
i SqlBackend
sb =
    SqlBackend
sb { connMaxParams :: Maybe Int
connMaxParams = forall a. a -> Maybe a
Just Int
i }
setConnRepsertManySql
    :: (EntityDef -> Int -> Text)
    -> SqlBackend
    -> SqlBackend
setConnRepsertManySql :: (EntityDef -> Int -> Text) -> SqlBackend -> SqlBackend
setConnRepsertManySql EntityDef -> Int -> Text
mkQuery SqlBackend
sb =
    SqlBackend
sb { connRepsertManySql :: Maybe (EntityDef -> Int -> Text)
connRepsertManySql = forall a. a -> Maybe a
Just EntityDef -> Int -> Text
mkQuery }
setConnInsertManySql
    :: (EntityDef -> [[PersistValue]] -> InsertSqlResult)
    -> SqlBackend
    -> SqlBackend
setConnInsertManySql :: (EntityDef -> [[PersistValue]] -> InsertSqlResult)
-> SqlBackend -> SqlBackend
setConnInsertManySql EntityDef -> [[PersistValue]] -> InsertSqlResult
mkQuery SqlBackend
sb =
    SqlBackend
sb { connInsertManySql :: Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
connInsertManySql = forall a. a -> Maybe a
Just EntityDef -> [[PersistValue]] -> InsertSqlResult
mkQuery }
setConnUpsertSql
    :: (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)
    -> SqlBackend
    -> SqlBackend
setConnUpsertSql :: (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)
-> SqlBackend -> SqlBackend
setConnUpsertSql EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text
mkQuery SqlBackend
sb =
    SqlBackend
sb { connUpsertSql :: Maybe
  (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)
connUpsertSql = forall a. a -> Maybe a
Just EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text
mkQuery }
setConnPutManySql
    :: (EntityDef -> Int -> Text)
    -> SqlBackend
    -> SqlBackend
setConnPutManySql :: (EntityDef -> Int -> Text) -> SqlBackend -> SqlBackend
setConnPutManySql  EntityDef -> Int -> Text
mkQuery SqlBackend
sb =
    SqlBackend
sb { connPutManySql :: Maybe (EntityDef -> Int -> Text)
connPutManySql = forall a. a -> Maybe a
Just EntityDef -> Int -> Text
mkQuery }
setConnVault :: Vault -> SqlBackend -> SqlBackend
setConnVault :: Vault -> SqlBackend -> SqlBackend
setConnVault Vault
vault SqlBackend
sb =
    SqlBackend
sb { connVault :: Vault
connVault = Vault
vault }
modifyConnVault :: (Vault -> Vault) -> SqlBackend  -> SqlBackend
modifyConnVault :: (Vault -> Vault) -> SqlBackend -> SqlBackend
modifyConnVault Vault -> Vault
f SqlBackend
sb =
    SqlBackend
sb { connVault :: Vault
connVault = Vault -> Vault
f forall a b. (a -> b) -> a -> b
$ SqlBackend -> Vault
connVault SqlBackend
sb }
setConnHooks :: SqlBackendHooks -> SqlBackend -> SqlBackend
setConnHooks :: SqlBackendHooks -> SqlBackend -> SqlBackend
setConnHooks SqlBackendHooks
hooks SqlBackend
sb =
    SqlBackend
sb { connHooks :: SqlBackendHooks
connHooks = SqlBackendHooks
hooks }