{-# language RecordWildCards #-}
{-# language RankNTypes #-}
module Database.Persist.SqlBackend.Internal where
import Data.Map (Map)
import Data.List.NonEmpty (NonEmpty)
import Data.Text (Text)
import Database.Persist.Class.PersistStore
import Database.Persist.Types.Base
import Database.Persist.Names
import Data.IORef
import Database.Persist.SqlBackend.Internal.MkSqlBackend
import Database.Persist.SqlBackend.Internal.Statement
import Database.Persist.SqlBackend.Internal.InsertSqlResult
import Database.Persist.SqlBackend.Internal.IsolationLevel
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 -> IORef (Map Text Statement)
connStmtMap :: IORef (Map Text Statement)
, 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)
}
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 :: (Text -> IO Statement)
-> (EntityDef -> [PersistValue] -> InsertSqlResult)
-> Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
-> Maybe
(EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> 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 ())
-> (FieldNameDB -> Text)
-> (EntityDef -> Text)
-> (Text -> Text)
-> Text
-> Text
-> ((Int, Int) -> Text -> Text)
-> LogFunc
-> Maybe Int
-> Maybe (EntityDef -> Int -> Text)
-> SqlBackend
SqlBackend
{ 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
, connPutManySql :: Maybe (EntityDef -> Int -> Text)
connPutManySql = Maybe (EntityDef -> Int -> Text)
forall a. Maybe a
Nothing
, connUpsertSql :: Maybe
(EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)
connUpsertSql = Maybe
(EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)
forall a. Maybe a
Nothing
, connInsertManySql :: Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
connInsertManySql = Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
forall a. Maybe a
Nothing
, 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 :: 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
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
..
}
instance HasPersistBackend SqlBackend where
type BaseBackend SqlBackend = SqlBackend
persistBackend :: SqlBackend -> BaseBackend SqlBackend
persistBackend = SqlBackend -> BaseBackend SqlBackend
forall a. a -> a
id
instance IsPersistBackend SqlBackend where
mkPersistBackend :: BaseBackend SqlBackend -> SqlBackend
mkPersistBackend = BaseBackend SqlBackend -> SqlBackend
forall a. a -> a
id