Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype PersistUnsafeMigrationException = PersistUnsafeMigrationException [(Bool, Sql)]
- newtype Single a = Single {
- unSingle :: a
- data ConnectionPoolConfig = ConnectionPoolConfig {}
- type ConnectionPool = Pool SqlBackend
- type Migration = WriterT [Text] (WriterT CautiousMigration (ReaderT SqlBackend IO)) ()
- type CautiousMigration = [(Bool, Sql)]
- type Sql = Text
- type SqlPersistM = SqlPersistT (NoLoggingT (ResourceT IO))
- type SqlPersistT = ReaderT SqlBackend
- data PersistentSqlException
- data ColumnReference = ColumnReference {}
- data Column = Column {}
- defaultConnectionPoolConfig :: ConnectionPoolConfig
- data SqlBackend = SqlBackend {
- connPrepare :: Text -> IO Statement
- connInsertSql :: EntityDef -> [PersistValue] -> InsertSqlResult
- connInsertManySql :: Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
- connUpsertSql :: Maybe (EntityDef -> NonEmpty (HaskellName, DBName) -> Text -> Text)
- connPutManySql :: Maybe (EntityDef -> Int -> Text)
- connStmtMap :: IORef (Map Text Statement)
- connClose :: IO ()
- connMigrateSql :: [EntityDef] -> (Text -> IO Statement) -> EntityDef -> IO (Either [Text] [(Bool, Text)])
- connBegin :: (Text -> IO Statement) -> Maybe IsolationLevel -> IO ()
- connCommit :: (Text -> IO Statement) -> IO ()
- connRollback :: (Text -> IO Statement) -> IO ()
- connEscapeName :: DBName -> Text
- connNoLimit :: Text
- connRDBMS :: Text
- connLimitOffset :: (Int, Int) -> Bool -> Text -> Text
- connLogFunc :: LogFunc
- connMaxParams :: Maybe Int
- connRepsertManySql :: Maybe (EntityDef -> Int -> Text)
- newtype SqlReadBackend = SqlReadBackend {}
- newtype SqlWriteBackend = SqlWriteBackend {}
- data Statement = Statement {
- stmtFinalize :: IO ()
- stmtReset :: IO ()
- stmtExecute :: [PersistValue] -> IO Int64
- stmtQuery :: forall m. MonadIO m => [PersistValue] -> Acquire (ConduitM () [PersistValue] m ())
- type LogFunc = Loc -> LogSource -> LogLevel -> LogStr -> IO ()
- data InsertSqlResult
- readToUnknown :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlBackend m a
- readToWrite :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlWriteBackend m a
- writeToUnknown :: Monad m => ReaderT SqlWriteBackend m a -> ReaderT SqlBackend m a
- type SqlBackendCanRead backend = (BackendCompatible SqlBackend backend, PersistQueryRead backend, PersistStoreRead backend, PersistUniqueRead backend)
- type SqlBackendCanWrite backend = (SqlBackendCanRead backend, PersistQueryWrite backend, PersistStoreWrite backend, PersistUniqueWrite backend)
- type SqlReadT m a = forall backend. SqlBackendCanRead backend => ReaderT backend m a
- type SqlWriteT m a = forall backend. SqlBackendCanWrite backend => ReaderT backend m a
- type IsSqlBackend backend = (IsPersistBackend backend, BaseBackend backend ~ SqlBackend)
- newtype OverflowNatural = OverflowNatural {}
- data ConnectionPoolConfig = ConnectionPoolConfig {}
- class RawSql a where
- rawSqlCols :: (DBName -> Text) -> a -> (Int, [Text])
- rawSqlColCountReason :: a -> String
- rawSqlProcessRow :: [PersistValue] -> Either Text a
- class PersistField a => PersistFieldSql a where
- newtype EntityWithPrefix (prefix :: Symbol) record = EntityWithPrefix {
- unEntityWithPrefix :: Entity record
- unPrefix :: forall prefix record. EntityWithPrefix prefix record -> Entity record
- unsafeAcquireSqlConnFromPool :: forall backend m. (MonadReader (Pool backend) m, BackendCompatible SqlBackend backend) => m (Acquire backend)
- acquireSqlConnFromPool :: (MonadReader (Pool backend) m, BackendCompatible SqlBackend backend) => m (Acquire backend)
- acquireSqlConnFromPoolWithIsolation :: (MonadReader (Pool backend) m, BackendCompatible SqlBackend backend) => IsolationLevel -> m (Acquire backend)
- runSqlPool :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> Pool backend -> m a
- runSqlPoolWithIsolation :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> Pool backend -> IsolationLevel -> m a
- acquireSqlConn :: (MonadReader backend m, BackendCompatible SqlBackend backend) => m (Acquire backend)
- acquireSqlConnWithIsolation :: (MonadReader backend m, BackendCompatible SqlBackend backend) => IsolationLevel -> m (Acquire backend)
- runSqlConn :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> backend -> m a
- runSqlConnWithIsolation :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> backend -> IsolationLevel -> m a
- runSqlPersistM :: BackendCompatible SqlBackend backend => ReaderT backend (NoLoggingT (ResourceT IO)) a -> backend -> IO a
- runSqlPersistMPool :: BackendCompatible SqlBackend backend => ReaderT backend (NoLoggingT (ResourceT IO)) a -> Pool backend -> IO a
- liftSqlPersistMPool :: forall backend m a. (MonadIO m, BackendCompatible SqlBackend backend) => ReaderT backend (NoLoggingT (ResourceT IO)) a -> Pool backend -> m a
- withSqlPool :: forall backend m a. (MonadLogger m, MonadUnliftIO m, BackendCompatible SqlBackend backend) => (LogFunc -> IO backend) -> Int -> (Pool backend -> m a) -> m a
- withSqlPoolWithConfig :: forall backend m a. (MonadLogger m, MonadUnliftIO m, BackendCompatible SqlBackend backend) => (LogFunc -> IO backend) -> ConnectionPoolConfig -> (Pool backend -> m a) -> m a
- createSqlPool :: forall backend m. (MonadLogger m, MonadUnliftIO m, BackendCompatible SqlBackend backend) => (LogFunc -> IO backend) -> Int -> m (Pool backend)
- createSqlPoolWithConfig :: forall m backend. (MonadLogger m, MonadUnliftIO m, BackendCompatible SqlBackend backend) => (LogFunc -> IO backend) -> ConnectionPoolConfig -> m (Pool backend)
- askLogFunc :: forall m. (MonadUnliftIO m, MonadLogger m) => m LogFunc
- withSqlConn :: forall backend m a. (MonadUnliftIO m, MonadLogger m, BackendCompatible SqlBackend backend) => (LogFunc -> IO backend) -> (backend -> m a) -> m a
- close' :: BackendCompatible SqlBackend backend => backend -> IO ()
- parseMigration :: (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m (Either [Text] CautiousMigration)
- parseMigration' :: (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m CautiousMigration
- printMigration :: (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m ()
- showMigration :: (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m [Text]
- getMigration :: (MonadIO m, HasCallStack) => Migration -> ReaderT SqlBackend m [Sql]
- runMigration :: MonadIO m => Migration -> ReaderT SqlBackend m ()
- runMigrationQuiet :: MonadIO m => Migration -> ReaderT SqlBackend m [Text]
- runMigrationSilent :: MonadUnliftIO m => Migration -> ReaderT SqlBackend m [Text]
- runMigrationUnsafe :: MonadIO m => Migration -> ReaderT SqlBackend m ()
- runMigrationUnsafeQuiet :: (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m [Text]
- migrate :: [EntityDef] -> EntityDef -> Migration
- reportErrors :: [Text] -> Migration
- reportError :: Text -> Migration
- addMigrations :: CautiousMigration -> Migration
- addMigration :: Bool -> Sql -> Migration
- module Database.Persist
- withRawQuery :: MonadIO m => Text -> [PersistValue] -> ConduitM [PersistValue] Void IO a -> ReaderT SqlBackend m a
- data family BackendKey backend
- toSqlKey :: ToBackendKey SqlBackend record => Int64 -> Key record
- fromSqlKey :: ToBackendKey SqlBackend record => Key record -> Int64
- getFieldName :: forall record typ m backend. (PersistEntity record, PersistEntityBackend record ~ SqlBackend, BackendCompatible SqlBackend backend, Monad m) => EntityField record typ -> ReaderT backend m Text
- getTableName :: forall record m backend. (PersistEntity record, BackendCompatible SqlBackend backend, Monad m) => record -> ReaderT backend m Text
- tableDBName :: PersistEntity record => record -> DBName
- fieldDBName :: forall record typ. PersistEntity record => EntityField record typ -> DBName
- rawQuery :: (MonadResource m, MonadReader env m, BackendCompatible SqlBackend env) => Text -> [PersistValue] -> ConduitM () [PersistValue] m ()
- rawQueryRes :: (MonadIO m1, MonadIO m2, BackendCompatible SqlBackend env) => Text -> [PersistValue] -> ReaderT env m1 (Acquire (ConduitM () [PersistValue] m2 ()))
- rawExecute :: (MonadIO m, BackendCompatible SqlBackend backend) => Text -> [PersistValue] -> ReaderT backend m ()
- rawExecuteCount :: (MonadIO m, BackendCompatible SqlBackend backend) => Text -> [PersistValue] -> ReaderT backend m Int64
- rawSql :: (RawSql a, MonadIO m, BackendCompatible SqlBackend backend) => Text -> [PersistValue] -> ReaderT backend m [a]
- deleteWhereCount :: (PersistEntity val, MonadIO m, PersistEntityBackend val ~ SqlBackend, BackendCompatible SqlBackend backend) => [Filter val] -> ReaderT backend m Int64
- updateWhereCount :: (PersistEntity val, MonadIO m, SqlBackend ~ PersistEntityBackend val, BackendCompatible SqlBackend backend) => [Filter val] -> [Update val] -> ReaderT backend m Int64
- transactionSave :: MonadIO m => ReaderT SqlBackend m ()
- transactionSaveWithIsolation :: MonadIO m => IsolationLevel -> ReaderT SqlBackend m ()
- transactionUndo :: MonadIO m => ReaderT SqlBackend m ()
- transactionUndoWithIsolation :: MonadIO m => IsolationLevel -> ReaderT SqlBackend m ()
- data IsolationLevel
- getStmtConn :: SqlBackend -> Text -> IO Statement
- mkColumns :: [EntityDef] -> EntityDef -> BackendSpecificOverrides -> ([Column], [UniqueDef], [ForeignDef])
- defaultAttribute :: [FieldAttr] -> Maybe Text
- data BackendSpecificOverrides = BackendSpecificOverrides {
- backendSpecificForeignKeyName :: Maybe (DBName -> DBName -> DBName)
- emptyBackendSpecificOverrides :: BackendSpecificOverrides
- decorateSQLWithLimitOffset :: Text -> (Int, Int) -> Bool -> Text -> Text
Documentation
newtype PersistUnsafeMigrationException Source #
An exception indicating that Persistent refused to run some unsafe migrations. Contains a list of pairs where the Bool tracks whether the migration was unsafe (True means unsafe), and the Sql is the sql statement for the migration.
Since: 2.11.1.0
Instances
Show PersistUnsafeMigrationException Source # | This |
Defined in Database.Persist.Sql.Types | |
Exception PersistUnsafeMigrationException Source # | |
A single column (see rawSql
). Any PersistField
may be
used here, including PersistValue
(which does not do any
processing).
Instances
Eq a => Eq (Single a) Source # | |
Ord a => Ord (Single a) Source # | |
Defined in Database.Persist.Sql.Types | |
Read a => Read (Single a) Source # | |
Show a => Show (Single a) Source # | |
PersistField a => RawSql (Single a) Source # | |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> Single a -> (Int, [Text]) Source # rawSqlColCountReason :: Single a -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (Single a) Source # |
data ConnectionPoolConfig Source #
Values to configure a pool of database connections. See Data.Pool for details.
Since: 2.11.0.0
ConnectionPoolConfig | |
|
Instances
Show ConnectionPoolConfig Source # | |
Defined in Database.Persist.Sql.Types showsPrec :: Int -> ConnectionPoolConfig -> ShowS # show :: ConnectionPoolConfig -> String # showList :: [ConnectionPoolConfig] -> ShowS # |
type ConnectionPool = Pool SqlBackend Source #
type Migration = WriterT [Text] (WriterT CautiousMigration (ReaderT SqlBackend IO)) () Source #
A Migration
is a four level monad stack consisting of:
representing a log of errors in the migrations.WriterT
[Text
]
representing a list of migrations to run, along with whether or not they are safe.WriterT
CautiousMigration
, aka theReaderT
SqlBackend
SqlPersistT
transformer for database interop.
for arbitrary IO.IO
type CautiousMigration = [(Bool, Sql)] Source #
type SqlPersistM = SqlPersistT (NoLoggingT (ResourceT IO)) Source #
type SqlPersistT = ReaderT SqlBackend Source #
data PersistentSqlException Source #
Instances
Show PersistentSqlException Source # | |
Defined in Database.Persist.Sql.Types showsPrec :: Int -> PersistentSqlException -> ShowS # show :: PersistentSqlException -> String # showList :: [PersistentSqlException] -> ShowS # | |
Exception PersistentSqlException Source # | |
data ColumnReference Source #
This value specifies how a field references another table.
Since: 2.11.0.0
ColumnReference | |
|
Instances
Eq ColumnReference Source # | |
Defined in Database.Persist.Sql.Types (==) :: ColumnReference -> ColumnReference -> Bool # (/=) :: ColumnReference -> ColumnReference -> Bool # | |
Ord ColumnReference Source # | |
Defined in Database.Persist.Sql.Types compare :: ColumnReference -> ColumnReference -> Ordering # (<) :: ColumnReference -> ColumnReference -> Bool # (<=) :: ColumnReference -> ColumnReference -> Bool # (>) :: ColumnReference -> ColumnReference -> Bool # (>=) :: ColumnReference -> ColumnReference -> Bool # max :: ColumnReference -> ColumnReference -> ColumnReference # min :: ColumnReference -> ColumnReference -> ColumnReference # | |
Show ColumnReference Source # | |
Defined in Database.Persist.Sql.Types showsPrec :: Int -> ColumnReference -> ShowS # show :: ColumnReference -> String # showList :: [ColumnReference] -> ShowS # |
defaultConnectionPoolConfig :: ConnectionPoolConfig Source #
Initializes a ConnectionPoolConfig with default values. See the documentation of ConnectionPoolConfig
for each field's default value.
Since: 2.11.0.0
data SqlBackend Source #
A SqlBackend
represents a handle or connection to a database. It
contains functions and values that allow databases to have more
optimized implementations, as well as references that benefit
performance and sharing.
A SqlBackend
is *not* thread-safe. You should not assume that
a SqlBackend
can be shared among threads and run concurrent queries.
This *will* result in problems. Instead, you should create a
, known as a Pool
SqlBackend
ConnectionPool
, and pass that around in
multi-threaded applications.
To run actions in the persistent
library, you should use the
runSqlConn
function. If you're using a multithreaded application, use
the runSqlPool
function.
SqlBackend | |
|
Instances
newtype SqlReadBackend Source #
An SQL backend which can only handle read queries
The constructor was exposed in 2.10.0.
Instances
newtype SqlWriteBackend Source #
An SQL backend which can handle read or write queries
The constructor was exposed in 2.10.0
Instances
Statement | |
|
readToUnknown :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlBackend m a Source #
Useful for running a read query against a backend with unknown capabilities.
readToWrite :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlWriteBackend m a Source #
Useful for running a read query against a backend with read and write capabilities.
writeToUnknown :: Monad m => ReaderT SqlWriteBackend m a -> ReaderT SqlBackend m a Source #
Useful for running a write query against an untagged backend with unknown capabilities.
type SqlBackendCanRead backend = (BackendCompatible SqlBackend backend, PersistQueryRead backend, PersistStoreRead backend, PersistUniqueRead backend) Source #
A constraint synonym which witnesses that a backend is SQL and can run read queries.
type SqlBackendCanWrite backend = (SqlBackendCanRead backend, PersistQueryWrite backend, PersistStoreWrite backend, PersistUniqueWrite backend) Source #
A constraint synonym which witnesses that a backend is SQL and can run read and write queries.
type SqlReadT m a = forall backend. SqlBackendCanRead backend => ReaderT backend m a Source #
Like SqlPersistT
but compatible with any SQL backend which can handle read queries.
type SqlWriteT m a = forall backend. SqlBackendCanWrite backend => ReaderT backend m a Source #
Like SqlPersistT
but compatible with any SQL backend which can handle read and write queries.
type IsSqlBackend backend = (IsPersistBackend backend, BaseBackend backend ~ SqlBackend) Source #
A backend which is a wrapper around SqlBackend
.
newtype OverflowNatural Source #
Prior to persistent-2.11.0
, we provided an instance of
PersistField
for the Natural
type. This was in error, because
Natural
represents an infinite value, and databases don't have
reasonable types for this.
The instance for Natural
used the Int64
underlying type, which will
cause underflow and overflow errors. This type has the exact same code
in the instances, and will work seamlessly.
A more appropriate type for this is the Word
series of types from
Data.Word. These have a bounded size, are guaranteed to be
non-negative, and are quite efficient for the database to store.
Since: 2.11.0
Instances
data ConnectionPoolConfig Source #
Values to configure a pool of database connections. See Data.Pool for details.
Since: 2.11.0.0
ConnectionPoolConfig | |
|
Instances
Show ConnectionPoolConfig Source # | |
Defined in Database.Persist.Sql.Types showsPrec :: Int -> ConnectionPoolConfig -> ShowS # show :: ConnectionPoolConfig -> String # showList :: [ConnectionPoolConfig] -> ShowS # |
Class for data types that may be retrived from a rawSql
query.
rawSqlCols :: (DBName -> Text) -> a -> (Int, [Text]) Source #
Number of columns that this data type needs and the list
of substitutions for SELECT
placeholders ??
.
rawSqlColCountReason :: a -> String Source #
A string telling the user why the column count is what it is.
rawSqlProcessRow :: [PersistValue] -> Either Text a Source #
Transform a row of the result into the data type.
Instances
RawSql a => RawSql (Maybe a) Source # | Since: 1.0.1 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> Maybe a -> (Int, [Text]) Source # rawSqlColCountReason :: Maybe a -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (Maybe a) Source # | |
(PersistEntity record, PersistEntityBackend record ~ backend, IsPersistBackend backend) => RawSql (Entity record) Source # | |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> Entity record -> (Int, [Text]) Source # rawSqlColCountReason :: Entity record -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (Entity record) Source # | |
(PersistEntity a, PersistEntityBackend a ~ backend, IsPersistBackend backend) => RawSql (Key a) Source # | |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> Key a -> (Int, [Text]) Source # rawSqlColCountReason :: Key a -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (Key a) Source # | |
PersistField a => RawSql (Single a) Source # | |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> Single a -> (Int, [Text]) Source # rawSqlColCountReason :: Single a -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (Single a) Source # | |
(RawSql a, RawSql b) => RawSql (a, b) Source # | |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b) Source # | |
(PersistEntity record, KnownSymbol prefix, PersistEntityBackend record ~ backend, IsPersistBackend backend) => RawSql (EntityWithPrefix prefix record) Source # | |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> EntityWithPrefix prefix record -> (Int, [Text]) Source # rawSqlColCountReason :: EntityWithPrefix prefix record -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (EntityWithPrefix prefix record) Source # | |
(RawSql a, RawSql b, RawSql c) => RawSql (a, b, c) Source # | |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d) => RawSql (a, b, c, d) Source # | |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e) => RawSql (a, b, c, d, e) Source # | |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f) => RawSql (a, b, c, d, e, f) Source # | |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g) => RawSql (a, b, c, d, e, f, g) Source # | |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h) => RawSql (a, b, c, d, e, f, g, h) Source # | |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i) => RawSql (a, b, c, d, e, f, g, h, i) Source # | Since: 2.10.2 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j) => RawSql (a, b, c, d, e, f, g, h, i, j) Source # | Since: 2.10.2 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k) => RawSql (a, b, c, d, e, f, g, h, i, j, k) Source # | Since: 2.10.2 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l) Source # | Since: 2.10.2 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3, RawSql f3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3, RawSql f3, RawSql g3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3, RawSql f3, RawSql g3, RawSql h3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3, RawSql f3, RawSql g3, RawSql h3, RawSql i3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3) Source # | |
(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j, RawSql k, RawSql l, RawSql m, RawSql n, RawSql o, RawSql p, RawSql q, RawSql r, RawSql s, RawSql t, RawSql u, RawSql v, RawSql w, RawSql x, RawSql y, RawSql z, RawSql a2, RawSql b2, RawSql c2, RawSql d2, RawSql e2, RawSql f2, RawSql g2, RawSql h2, RawSql i2, RawSql j2, RawSql k2, RawSql l2, RawSql m2, RawSql n2, RawSql o2, RawSql p2, RawSql q2, RawSql r2, RawSql s2, RawSql t2, RawSql u2, RawSql v2, RawSql w2, RawSql x2, RawSql y2, RawSql z2, RawSql a3, RawSql b3, RawSql c3, RawSql d3, RawSql e3, RawSql f3, RawSql g3, RawSql h3, RawSql i3, RawSql j3) => RawSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3, j3) Source # | Since: 2.11.0 |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3, j3) -> (Int, [Text]) Source # rawSqlColCountReason :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3, j3) -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, a2, b2, c2, d2, e2, f2, g2, h2, i2, j2, k2, l2, m2, n2, o2, p2, q2, r2, s2, t2, u2, v2, w2, x2, y2, z2, a3, b3, c3, d3, e3, f3, g3, h3, i3, j3) Source # |
class PersistField a => PersistFieldSql a where Source #
Tells Persistent what database column type should be used to store a Haskell type.
Examples
Simple Boolean Alternative
data Switch = On | Off deriving (Show, Eq) instancePersistField
Switch wheretoPersistValue
s = case s of On ->PersistBool
True Off ->PersistBool
FalsefromPersistValue
(PersistBool
b) = if b thenRight
On elseRight
OfffromPersistValue
x = Left $ "File.hs: When trying to deserialize a Switch: expected PersistBool, received: " <> T.pack (show x) instancePersistFieldSql
Switch wheresqlType
_ =SqlBool
Non-Standard Database Types
If your database supports non-standard types, such as Postgres' uuid
, you can use SqlOther
to use them:
import qualified Data.UUID as UUID instancePersistField
UUID wheretoPersistValue
=PersistDbSpecific
. toASCIIBytesfromPersistValue
(PersistDbSpecific
uuid) = case fromASCIIBytes uuid ofNothing
->Left
$ "Model/CustomTypes.hs: Failed to deserialize a UUID; received: " <> T.pack (show uuid)Just
uuid' ->Right
uuid'fromPersistValue
x = Left $ "File.hs: When trying to deserialize a UUID: expected PersistDbSpecific, received: "-- > <> T.pack (show x) instancePersistFieldSql
UUID wheresqlType
_ =SqlOther
"uuid"
User Created Database Types
Similarly, some databases support creating custom types, e.g. Postgres' DOMAIN and ENUM features. You can use SqlOther
to specify a custom type:
CREATE DOMAIN ssn AS text CHECK ( value ~ '^[0-9]{9}$');
instancePersistFieldSQL
SSN wheresqlType
_ =SqlOther
"ssn"
CREATE TYPE rainbow_color AS ENUM ('red', 'orange', 'yellow', 'green', 'blue', 'indigo', 'violet');
instancePersistFieldSQL
RainbowColor wheresqlType
_ =SqlOther
"rainbow_color"
Instances
newtype EntityWithPrefix (prefix :: Symbol) record Source #
This newtype wrapper is useful when selecting an entity out of the database and you want to provide a prefix to the table being selected.
Consider this raw SQL query:
SELECT ?? FROM my_long_table_name AS mltn INNER JOIN other_table AS ot ON mltn.some_col = ot.other_col WHERE ...
We don't want to refer to my_long_table_name
every time, so we create
an alias. If we want to select it, we have to tell the raw SQL
quasi-quoter that we expect the entity to be prefixed with some other
name.
We can give the above query a type with this, like:
getStuff ::SqlPersistM
[EntityWithPrefix
"mltn" MyLongTableName] getStuff = rawSql queryText []
The EntityWithPrefix
bit is a boilerplate newtype wrapper, so you can
remove it with unPrefix
, like this:
getStuff ::SqlPersistM
[Entity
MyLongTableName] getStuff =unPrefix
@"mltn"<$>
rawSql
queryText []
The symbol is a "type application" and requires the
TypeApplications@
language extension.
Since: 2.10.5
EntityWithPrefix | |
|
Instances
(PersistEntity record, KnownSymbol prefix, PersistEntityBackend record ~ backend, IsPersistBackend backend) => RawSql (EntityWithPrefix prefix record) Source # | |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> EntityWithPrefix prefix record -> (Int, [Text]) Source # rawSqlColCountReason :: EntityWithPrefix prefix record -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (EntityWithPrefix prefix record) Source # |
unPrefix :: forall prefix record. EntityWithPrefix prefix record -> Entity record Source #
A helper function to tell GHC what the EntityWithPrefix
prefix
should be. This allows you to use a type application to specify the
prefix, instead of specifying the etype on the result.
As an example, here's code that uses this:
myQuery ::SqlPersistM
[Entity
Person] myQuery = map (unPrefix @"p") $ rawSql query [] where query = "SELECT ?? FROM person AS p"
Since: 2.10.5
unsafeAcquireSqlConnFromPool :: forall backend m. (MonadReader (Pool backend) m, BackendCompatible SqlBackend backend) => m (Acquire backend) Source #
The returned Acquire
gets a connection from the pool, but does NOT
start a new transaction. Used to implement acquireSqlConnFromPool
and
acquireSqlConnFromPoolWithIsolation
, this is useful for performing actions
on a connection that cannot be done within a transaction, such as VACUUM in
Sqlite.
Since: 2.10.5
acquireSqlConnFromPool :: (MonadReader (Pool backend) m, BackendCompatible SqlBackend backend) => m (Acquire backend) Source #
The returned Acquire
gets a connection from the pool, starts a new
transaction and gives access to the prepared connection.
When the acquired connection is released the transaction is committed and the connection returned to the pool.
Upon an exception the transaction is rolled back and the connection destroyed.
This is equivalent to runSqlPool
but does not incur the MonadUnliftIO
constraint, meaning it can be used within, for example, a Conduit
pipeline.
Since: 2.10.5
acquireSqlConnFromPoolWithIsolation :: (MonadReader (Pool backend) m, BackendCompatible SqlBackend backend) => IsolationLevel -> m (Acquire backend) Source #
Like acquireSqlConnFromPool
, but lets you specify an explicit isolation
level.
Since: 2.10.5
runSqlPool :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> Pool backend -> m a Source #
Get a connection from the pool, run the given action, and then return the connection to the pool.
Note: This function previously timed out after 2 seconds, but this behavior was buggy and caused more problems than it solved. Since version 2.1.2, it performs no timeout checks.
runSqlPoolWithIsolation :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> Pool backend -> IsolationLevel -> m a Source #
Like runSqlPool
, but supports specifying an isolation level.
Since: 2.9.0
acquireSqlConn :: (MonadReader backend m, BackendCompatible SqlBackend backend) => m (Acquire backend) Source #
Starts a new transaction on the connection. When the acquired connection is released the transaction is committed and the connection returned to the pool.
Upon an exception the transaction is rolled back and the connection destroyed.
This is equivalent to 'runSqlConn but does not incur the MonadUnliftIO
constraint, meaning it can be used within, for example, a Conduit
pipeline.
Since: 2.10.5
acquireSqlConnWithIsolation :: (MonadReader backend m, BackendCompatible SqlBackend backend) => IsolationLevel -> m (Acquire backend) Source #
Like acquireSqlConn
, but lets you specify an explicit isolation level.
Since: 2.10.5
runSqlConn :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> backend -> m a Source #
runSqlConnWithIsolation :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> backend -> IsolationLevel -> m a Source #
Like runSqlConn
, but supports specifying an isolation level.
Since: 2.9.0
runSqlPersistM :: BackendCompatible SqlBackend backend => ReaderT backend (NoLoggingT (ResourceT IO)) a -> backend -> IO a Source #
runSqlPersistMPool :: BackendCompatible SqlBackend backend => ReaderT backend (NoLoggingT (ResourceT IO)) a -> Pool backend -> IO a Source #
liftSqlPersistMPool :: forall backend m a. (MonadIO m, BackendCompatible SqlBackend backend) => ReaderT backend (NoLoggingT (ResourceT IO)) a -> Pool backend -> m a Source #
:: forall backend m a. (MonadLogger m, MonadUnliftIO m, BackendCompatible SqlBackend backend) | |
=> (LogFunc -> IO backend) | create a new connection |
-> Int | connection count |
-> (Pool backend -> m a) | |
-> m a |
withSqlPoolWithConfig Source #
:: forall backend m a. (MonadLogger m, MonadUnliftIO m, BackendCompatible SqlBackend backend) | |
=> (LogFunc -> IO backend) | Function to create a new connection |
-> ConnectionPoolConfig | |
-> (Pool backend -> m a) | |
-> m a |
Creates a pool of connections to a SQL database which can be used by the Pool backend -> m a
function.
After the function completes, the connections are destroyed.
Since: 2.11.0.0
createSqlPool :: forall backend m. (MonadLogger m, MonadUnliftIO m, BackendCompatible SqlBackend backend) => (LogFunc -> IO backend) -> Int -> m (Pool backend) Source #
createSqlPoolWithConfig Source #
:: forall m backend. (MonadLogger m, MonadUnliftIO m, BackendCompatible SqlBackend backend) | |
=> (LogFunc -> IO backend) | Function to create a new connection |
-> ConnectionPoolConfig | |
-> m (Pool backend) |
Creates a pool of connections to a SQL database.
Since: 2.11.0.0
askLogFunc :: forall m. (MonadUnliftIO m, MonadLogger m) => m LogFunc Source #
withSqlConn :: forall backend m a. (MonadUnliftIO m, MonadLogger m, BackendCompatible SqlBackend backend) => (LogFunc -> IO backend) -> (backend -> m a) -> m a Source #
Create a connection and run sql queries within it. This function automatically closes the connection on it's completion.
Example usage
{-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies#-} {-# LANGUAGE TemplateHaskell#-} {-# LANGUAGE QuasiQuotes#-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} import Control.Monad.IO.Class (liftIO) import Control.Monad.Logger import Conduit import Database.Persist import Database.Sqlite import Database.Persist.Sqlite import Database.Persist.TH share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase| Person name String age Int Maybe deriving Show |] openConnection :: LogFunc -> IO SqlBackend openConnection logfn = do conn <- open "/home/sibi/test.db" wrapConnection conn logfn main :: IO () main = do runNoLoggingT $ runResourceT $ withSqlConn openConnection (\backend -> flip runSqlConn backend $ do runMigration migrateAll insert_ $ Person "John doe" $ Just 35 insert_ $ Person "Divya" $ Just 36 (pers :: [Entity Person]) <- selectList [] [] liftIO $ print pers return () )
On executing it, you get this output:
Migrating: CREATE TABLE "person"("id" INTEGER PRIMARY KEY,"name" VARCHAR NOT NULL,"age" INTEGER NULL) [Entity {entityKey = PersonKey {unPersonKey = SqlBackendKey {unSqlBackendKey = 1}}, entityVal = Person {personName = "John doe", personAge = Just 35}},Entity {entityKey = PersonKey {unPersonKey = SqlBackendKey {unSqlBackendKey = 2}}, entityVal = Person {personName = "Hema", personAge = Just 36}}]
close' :: BackendCompatible SqlBackend backend => backend -> IO () Source #
parseMigration :: (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m (Either [Text] CautiousMigration) Source #
Given a Migration
, this parses it and returns either a list of
errors associated with the migration or a list of migrations to do.
parseMigration' :: (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m CautiousMigration Source #
Like parseMigration
, but instead of returning the value in an
Either
value, it calls error
on the error values.
printMigration :: (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m () Source #
Prints a migration.
showMigration :: (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m [Text] Source #
getMigration :: (MonadIO m, HasCallStack) => Migration -> ReaderT SqlBackend m [Sql] Source #
runMigration :: MonadIO m => Migration -> ReaderT SqlBackend m () Source #
Runs a migration. If the migration fails to parse or if any of the
migrations are unsafe, then this throws a PersistUnsafeMigrationException
.
runMigrationQuiet :: MonadIO m => Migration -> ReaderT SqlBackend m [Text] Source #
Same as runMigration
, but does not report the individual migrations on
stderr. Instead it returns a list of the executed SQL commands.
This is a safer/more robust alternative to runMigrationSilent
, but may be
less silent for some persistent implementations, most notably
persistent-postgresql
Since: 2.10.2
runMigrationSilent :: MonadUnliftIO m => Migration -> ReaderT SqlBackend m [Text] Source #
Same as runMigration
, but returns a list of the SQL commands executed
instead of printing them to stderr.
This function silences the migration by remapping stderr
. As a result, it
is not thread-safe and can clobber output from other parts of the program.
This implementation method was chosen to also silence postgresql migration
output on stderr, but is not recommended!
runMigrationUnsafe :: MonadIO m => Migration -> ReaderT SqlBackend m () Source #
Like runMigration
, but this will perform the unsafe database
migrations instead of erroring out.
runMigrationUnsafeQuiet :: (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m [Text] Source #
Same as runMigrationUnsafe
, but returns a list of the SQL commands
executed instead of printing them to stderr.
Since: 2.10.2
Utilities for constructing migrations
addMigrations :: CautiousMigration -> Migration Source #
Add a CautiousMigration
(aka a [(
) to the
migration plan.Bool
, Text
)]
Since: 2.9.2
:: Bool | Is the migration safe to run? (eg a non-destructive and idempotent update on the schema) |
-> Sql | A |
-> Migration |
Add a migration to the migration plan.
Since: 2.9.2
module Database.Persist
withRawQuery :: MonadIO m => Text -> [PersistValue] -> ConduitM [PersistValue] Void IO a -> ReaderT SqlBackend m a Source #
data family BackendKey backend Source #
Instances
toSqlKey :: ToBackendKey SqlBackend record => Int64 -> Key record Source #
fromSqlKey :: ToBackendKey SqlBackend record => Key record -> Int64 Source #
getFieldName :: forall record typ m backend. (PersistEntity record, PersistEntityBackend record ~ SqlBackend, BackendCompatible SqlBackend backend, Monad m) => EntityField record typ -> ReaderT backend m Text Source #
get the SQL string for the field that an EntityField represents Useful for raw SQL queries
Your backend may provide a more convenient fieldName function which does not operate in a Monad
getTableName :: forall record m backend. (PersistEntity record, BackendCompatible SqlBackend backend, Monad m) => record -> ReaderT backend m Text Source #
get the SQL string for the table that a PeristEntity represents Useful for raw SQL queries
Your backend may provide a more convenient tableName function which does not operate in a Monad
tableDBName :: PersistEntity record => record -> DBName Source #
useful for a backend to implement tableName by adding escaping
fieldDBName :: forall record typ. PersistEntity record => EntityField record typ -> DBName Source #
useful for a backend to implement fieldName by adding escaping
rawQuery :: (MonadResource m, MonadReader env m, BackendCompatible SqlBackend env) => Text -> [PersistValue] -> ConduitM () [PersistValue] m () Source #
rawQueryRes :: (MonadIO m1, MonadIO m2, BackendCompatible SqlBackend env) => Text -> [PersistValue] -> ReaderT env m1 (Acquire (ConduitM () [PersistValue] m2 ())) Source #
:: (MonadIO m, BackendCompatible SqlBackend backend) | |
=> Text | SQL statement, possibly with placeholders. |
-> [PersistValue] | Values to fill the placeholders. |
-> ReaderT backend m () |
Execute a raw SQL statement
:: (MonadIO m, BackendCompatible SqlBackend backend) | |
=> Text | SQL statement, possibly with placeholders. |
-> [PersistValue] | Values to fill the placeholders. |
-> ReaderT backend m Int64 |
Execute a raw SQL statement and return the number of rows it has modified.
:: (RawSql a, MonadIO m, BackendCompatible SqlBackend backend) | |
=> Text | SQL statement, possibly with placeholders. |
-> [PersistValue] | Values to fill the placeholders. |
-> ReaderT backend m [a] |
Execute a raw SQL statement and return its results as a
list. If you do not expect a return value, use of
rawExecute
is recommended.
If you're using Entity
s
(which is quite likely), then you
must use entity selection placeholders (double question
mark, ??
). These ??
placeholders are then replaced for
the names of the columns that we need for your entities.
You'll receive an error if you don't use the placeholders.
Please see the Entity
s
documentation for more details.
You may put value placeholders (question marks, ?
) in your
SQL query. These placeholders are then replaced by the values
you pass on the second parameter, already correctly escaped.
You may want to use toPersistValue
to help you constructing
the placeholder values.
Since you're giving a raw SQL statement, you don't get any
guarantees regarding safety. If rawSql
is not able to parse
the results of your query back, then an exception is raised.
However, most common problems are mitigated by using the
entity selection placeholder ??
, and you shouldn't see any
error at all if you're not using Single
.
Some example of rawSql
based on this schema:
share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase| Person name String age Int Maybe deriving Show BlogPost title String authorId PersonId deriving Show |]
Examples based on the above schema:
getPerson :: MonadIO m => ReaderT SqlBackend m [Entity Person] getPerson = rawSql "select ?? from person where name=?" [PersistText "john"] getAge :: MonadIO m => ReaderT SqlBackend m [Single Int] getAge = rawSql "select person.age from person where name=?" [PersistText "john"] getAgeName :: MonadIO m => ReaderT SqlBackend m [(Single Int, Single Text)] getAgeName = rawSql "select person.age, person.name from person where name=?" [PersistText "john"] getPersonBlog :: MonadIO m => ReaderT SqlBackend m [(Entity Person, Entity BlogPost)] getPersonBlog = rawSql "select ??,?? from person,blog_post where person.id = blog_post.author_id" []
Minimal working program for PostgreSQL backend based on the above concepts:
{-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} import Control.Monad.IO.Class (liftIO) import Control.Monad.Logger (runStderrLoggingT) import Database.Persist import Control.Monad.Reader import Data.Text import Database.Persist.Sql import Database.Persist.Postgresql import Database.Persist.TH share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase| Person name String age Int Maybe deriving Show |] conn = "host=localhost dbname=new_db user=postgres password=postgres port=5432" getPerson :: MonadIO m => ReaderT SqlBackend m [Entity Person] getPerson = rawSql "select ?? from person where name=?" [PersistText "sibi"] liftSqlPersistMPool y x = liftIO (runSqlPersistMPool y x) main :: IO () main = runStderrLoggingT $ withPostgresqlPool conn 10 $ liftSqlPersistMPool $ do runMigration migrateAll xs <- getPerson liftIO (print xs)
deleteWhereCount :: (PersistEntity val, MonadIO m, PersistEntityBackend val ~ SqlBackend, BackendCompatible SqlBackend backend) => [Filter val] -> ReaderT backend m Int64 Source #
Same as deleteWhere
, but returns the number of rows affected.
Since: 1.1.5
updateWhereCount :: (PersistEntity val, MonadIO m, SqlBackend ~ PersistEntityBackend val, BackendCompatible SqlBackend backend) => [Filter val] -> [Update val] -> ReaderT backend m Int64 Source #
Same as updateWhere
, but returns the number of rows affected.
Since: 1.1.5
transactionSave :: MonadIO m => ReaderT SqlBackend m () Source #
Commit the current transaction and begin a new one.
This is used when a transaction commit is required within the context of runSqlConn
(which brackets its provided action with a transaction begin/commit pair).
Since: 1.2.0
transactionSaveWithIsolation :: MonadIO m => IsolationLevel -> ReaderT SqlBackend m () Source #
Commit the current transaction and begin a new one with the specified isolation level.
Since: 2.9.0
transactionUndo :: MonadIO m => ReaderT SqlBackend m () Source #
Roll back the current transaction and begin a new one.
This rolls back to the state of the last call to transactionSave
or the enclosing
runSqlConn
call.
Since: 1.2.0
transactionUndoWithIsolation :: MonadIO m => IsolationLevel -> ReaderT SqlBackend m () Source #
Roll back the current transaction and begin a new one with the specified isolation level.
Since: 2.9.0
data IsolationLevel Source #
Please refer to the documentation for the database in question for a full overview of the semantics of the varying isloation levels
Instances
getStmtConn :: SqlBackend -> Text -> IO Statement Source #
Internal
mkColumns :: [EntityDef] -> EntityDef -> BackendSpecificOverrides -> ([Column], [UniqueDef], [ForeignDef]) Source #
Create the list of columns for the given entity.
data BackendSpecificOverrides Source #
Record of functions to override the default behavior in mkColumns
.
It is recommended you initialize this with emptyBackendSpecificOverrides
and override the default values,
so that as new fields are added, your code still compiles.
Since: 2.11
emptyBackendSpecificOverrides :: BackendSpecificOverrides Source #
Creates an empty BackendSpecificOverrides
(i.e. use the default behavior; no overrides)
Since: 2.11