{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
module Database.Persist.SqlBackend.Internal where
import Data.List.NonEmpty (NonEmpty)
import Data.Text (Text)
import Data.Vault.Strict (Vault)
import qualified Data.Vault.Strict as Vault
import Database.Persist.Class.PersistStore
import Database.Persist.Names
import Database.Persist.SqlBackend.Internal.InsertSqlResult
import Database.Persist.SqlBackend.Internal.IsolationLevel
import Database.Persist.SqlBackend.Internal.MkSqlBackend
import Database.Persist.SqlBackend.Internal.Statement
import Database.Persist.SqlBackend.StatementCache
import Database.Persist.Types.Base
data SqlBackend = SqlBackend
    { SqlBackend -> Text -> IO Statement
connPrepare :: Text -> IO Statement
    
    
    , SqlBackend -> EntityDef -> [PersistValue] -> InsertSqlResult
connInsertSql :: EntityDef -> [PersistValue] -> InsertSqlResult
    
    
    , SqlBackend
-> Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
connInsertManySql :: Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
    
    
    
    , SqlBackend
-> Maybe
     (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)
connUpsertSql :: Maybe (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)
    
    
    
    
    
    
    
    
    
    
    
    
    
    , SqlBackend -> Maybe (EntityDef -> Int -> Text)
connPutManySql :: Maybe (EntityDef -> Int -> Text)
    
    
    
    
    
    
    
    
    
    
    
    , SqlBackend -> StatementCache
connStmtMap :: StatementCache
    
    
    , SqlBackend -> IO ()
connClose :: IO ()
    
    , SqlBackend
-> [EntityDef]
-> (Text -> IO Statement)
-> EntityDef
-> IO (Either [Text] [(Bool, Text)])
connMigrateSql
        :: [EntityDef]
        -> (Text -> IO Statement)
        -> EntityDef
        -> IO (Either [Text] [(Bool, Text)])
    
    
    
    
    , SqlBackend
-> (Text -> IO Statement) -> Maybe IsolationLevel -> IO ()
connBegin :: (Text -> IO Statement) -> Maybe IsolationLevel -> IO ()
    
    , SqlBackend -> (Text -> IO Statement) -> IO ()
connCommit :: (Text -> IO Statement) -> IO ()
    
    , SqlBackend -> (Text -> IO Statement) -> IO ()
connRollback :: (Text -> IO Statement) -> IO ()
    
    , SqlBackend -> FieldNameDB -> Text
connEscapeFieldName :: FieldNameDB -> Text
    
    
    
    
    , SqlBackend -> EntityDef -> Text
connEscapeTableName :: EntityDef -> Text
    
    
    
    
    , SqlBackend -> Text -> Text
connEscapeRawName :: Text -> Text
    
    
    
    
    , SqlBackend -> Text
connNoLimit :: Text
    , SqlBackend -> Text
connRDBMS :: Text
    
    
    
    , SqlBackend -> (Int, Int) -> Text -> Text
connLimitOffset :: (Int,Int) -> Text -> Text
    
    
    
    , SqlBackend -> LogFunc
connLogFunc :: LogFunc
    
    , SqlBackend -> Maybe Int
connMaxParams :: Maybe Int
    
    
    
    
    , SqlBackend -> Maybe (EntityDef -> Int -> Text)
connRepsertManySql :: Maybe (EntityDef -> Int -> Text)
    
    
    
    
    
    
    
    
    
    
    
    , SqlBackend -> Vault
connVault :: Vault
    
    
    , SqlBackend -> SqlBackendHooks
connHooks :: SqlBackendHooks
    
    
    }
newtype SqlBackendHooks = SqlBackendHooks
    { SqlBackendHooks -> SqlBackend -> Text -> Statement -> IO Statement
hookGetStatement :: SqlBackend -> Text -> Statement -> IO Statement
    }
emptySqlBackendHooks :: SqlBackendHooks
emptySqlBackendHooks :: SqlBackendHooks
emptySqlBackendHooks = SqlBackendHooks
    { hookGetStatement :: SqlBackend -> Text -> Statement -> IO Statement
hookGetStatement = \SqlBackend
_ Text
_ Statement
s -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Statement
s
    }
mkSqlBackend :: MkSqlBackendArgs -> SqlBackend
mkSqlBackend :: MkSqlBackendArgs -> SqlBackend
mkSqlBackend MkSqlBackendArgs {IO ()
Text
IORef (Map Text Statement)
[EntityDef]
-> (Text -> IO Statement)
-> EntityDef
-> IO (Either [Text] [(Bool, Text)])
(Int, Int) -> Text -> Text
Text -> IO Statement
Text -> Text
LogFunc
FieldNameDB -> Text
EntityDef -> Text
EntityDef -> [PersistValue] -> InsertSqlResult
(Text -> IO Statement) -> IO ()
(Text -> IO Statement) -> Maybe IsolationLevel -> IO ()
connLogFunc :: MkSqlBackendArgs -> LogFunc
connLimitOffset :: MkSqlBackendArgs -> (Int, Int) -> Text -> Text
connRDBMS :: MkSqlBackendArgs -> Text
connNoLimit :: MkSqlBackendArgs -> Text
connEscapeRawName :: MkSqlBackendArgs -> Text -> Text
connEscapeTableName :: MkSqlBackendArgs -> EntityDef -> Text
connEscapeFieldName :: MkSqlBackendArgs -> FieldNameDB -> Text
connRollback :: MkSqlBackendArgs -> (Text -> IO Statement) -> IO ()
connCommit :: MkSqlBackendArgs -> (Text -> IO Statement) -> IO ()
connBegin :: MkSqlBackendArgs
-> (Text -> IO Statement) -> Maybe IsolationLevel -> IO ()
connMigrateSql :: MkSqlBackendArgs
-> [EntityDef]
-> (Text -> IO Statement)
-> EntityDef
-> IO (Either [Text] [(Bool, Text)])
connClose :: MkSqlBackendArgs -> IO ()
connStmtMap :: MkSqlBackendArgs -> IORef (Map Text Statement)
connInsertSql :: MkSqlBackendArgs -> EntityDef -> [PersistValue] -> InsertSqlResult
connPrepare :: MkSqlBackendArgs -> Text -> IO Statement
connLogFunc :: LogFunc
connLimitOffset :: (Int, Int) -> Text -> Text
connRDBMS :: Text
connNoLimit :: Text
connEscapeRawName :: Text -> Text
connEscapeTableName :: EntityDef -> Text
connEscapeFieldName :: FieldNameDB -> Text
connRollback :: (Text -> IO Statement) -> IO ()
connCommit :: (Text -> IO Statement) -> IO ()
connBegin :: (Text -> IO Statement) -> Maybe IsolationLevel -> IO ()
connMigrateSql :: [EntityDef]
-> (Text -> IO Statement)
-> EntityDef
-> IO (Either [Text] [(Bool, Text)])
connClose :: IO ()
connStmtMap :: IORef (Map Text Statement)
connInsertSql :: EntityDef -> [PersistValue] -> InsertSqlResult
connPrepare :: Text -> IO Statement
..} =
    SqlBackend
        { connMaxParams :: Maybe Int
connMaxParams = forall a. Maybe a
Nothing
        , connRepsertManySql :: Maybe (EntityDef -> Int -> Text)
connRepsertManySql = forall a. Maybe a
Nothing
        , connPutManySql :: Maybe (EntityDef -> Int -> Text)
connPutManySql = forall a. Maybe a
Nothing
        , connUpsertSql :: Maybe
  (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)
connUpsertSql = forall a. Maybe a
Nothing
        , connInsertManySql :: Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
connInsertManySql = forall a. Maybe a
Nothing
        , connVault :: Vault
connVault = Vault
Vault.empty
        , connHooks :: SqlBackendHooks
connHooks = SqlBackendHooks
emptySqlBackendHooks
        , connStmtMap :: StatementCache
connStmtMap = MkStatementCache -> StatementCache
mkStatementCache forall a b. (a -> b) -> a -> b
$ IORef (Map Text Statement) -> MkStatementCache
mkSimpleStatementCache IORef (Map Text Statement)
connStmtMap
        , IO ()
Text
[EntityDef]
-> (Text -> IO Statement)
-> EntityDef
-> IO (Either [Text] [(Bool, Text)])
(Int, Int) -> Text -> Text
Text -> IO Statement
Text -> Text
LogFunc
FieldNameDB -> Text
EntityDef -> Text
EntityDef -> [PersistValue] -> InsertSqlResult
(Text -> IO Statement) -> IO ()
(Text -> IO Statement) -> Maybe IsolationLevel -> IO ()
connLogFunc :: LogFunc
connLimitOffset :: (Int, Int) -> Text -> Text
connRDBMS :: Text
connNoLimit :: Text
connEscapeRawName :: Text -> Text
connEscapeTableName :: EntityDef -> Text
connEscapeFieldName :: FieldNameDB -> Text
connRollback :: (Text -> IO Statement) -> IO ()
connCommit :: (Text -> IO Statement) -> IO ()
connBegin :: (Text -> IO Statement) -> Maybe IsolationLevel -> IO ()
connMigrateSql :: [EntityDef]
-> (Text -> IO Statement)
-> EntityDef
-> IO (Either [Text] [(Bool, Text)])
connClose :: IO ()
connInsertSql :: EntityDef -> [PersistValue] -> InsertSqlResult
connPrepare :: Text -> IO Statement
connLogFunc :: LogFunc
connLimitOffset :: (Int, Int) -> Text -> Text
connRDBMS :: Text
connNoLimit :: Text
connEscapeRawName :: Text -> Text
connEscapeTableName :: EntityDef -> Text
connEscapeFieldName :: FieldNameDB -> Text
connRollback :: (Text -> IO Statement) -> IO ()
connCommit :: (Text -> IO Statement) -> IO ()
connBegin :: (Text -> IO Statement) -> Maybe IsolationLevel -> IO ()
connMigrateSql :: [EntityDef]
-> (Text -> IO Statement)
-> EntityDef
-> IO (Either [Text] [(Bool, Text)])
connClose :: IO ()
connInsertSql :: EntityDef -> [PersistValue] -> InsertSqlResult
connPrepare :: Text -> IO Statement
..
        }
instance HasPersistBackend SqlBackend where
    type BaseBackend SqlBackend = SqlBackend
    persistBackend :: SqlBackend -> BaseBackend SqlBackend
persistBackend = forall a. a -> a
id
instance IsPersistBackend SqlBackend where
    mkPersistBackend :: BaseBackend SqlBackend -> SqlBackend
mkPersistBackend = forall a. a -> a
id