Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module contain PostgreSQL-specific functions.
Since: 2.2.8
Synopsis
- data AggMode
- arrayAggDistinct :: (PersistField a, PersistField [a]) => SqlExpr (Value a) -> SqlExpr (Value (Maybe [a]))
- arrayAgg :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value (Maybe [a]))
- arrayAggWith :: AggMode -> SqlExpr (Value a) -> [OrderByClause] -> SqlExpr (Value (Maybe [a]))
- arrayRemove :: SqlExpr (Value [a]) -> SqlExpr (Value a) -> SqlExpr (Value [a])
- arrayRemoveNull :: SqlExpr (Value [Maybe a]) -> SqlExpr (Value [a])
- stringAgg :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value (Maybe s))
- stringAggWith :: SqlString s => AggMode -> SqlExpr (Value s) -> SqlExpr (Value s) -> [OrderByClause] -> SqlExpr (Value (Maybe s))
- maybeArray :: (PersistField a, PersistField [a]) => SqlExpr (Value (Maybe [a])) -> SqlExpr (Value [a])
- chr :: SqlString s => SqlExpr (Value Int) -> SqlExpr (Value s)
- now_ :: SqlExpr (Value UTCTime)
- random_ :: (PersistField a, Num a) => SqlExpr (Value a)
- upsert :: (MonadIO m, PersistEntity record, OnlyOneUniqueKey record, PersistRecordBackend record SqlBackend, IsPersistBackend (PersistEntityBackend record)) => record -> [SqlExpr (Update record)] -> ReaderT SqlBackend m (Entity record)
- upsertBy :: (MonadIO m, PersistEntity record, IsPersistBackend (PersistEntityBackend record)) => Unique record -> record -> [SqlExpr (Update record)] -> ReaderT SqlBackend m (Entity record)
- insertSelectWithConflict :: forall a m val. (FinalResult a, KnowResult a ~ Unique val, MonadIO m, PersistEntity val) => a -> SqlQuery (SqlExpr (Insertion val)) -> (SqlExpr (Entity val) -> SqlExpr (Entity val) -> [SqlExpr (Update val)]) -> SqlWriteT m ()
- insertSelectWithConflictCount :: forall a val m. (FinalResult a, KnowResult a ~ Unique val, MonadIO m, PersistEntity val) => a -> SqlQuery (SqlExpr (Insertion val)) -> (SqlExpr (Entity val) -> SqlExpr (Entity val) -> [SqlExpr (Update val)]) -> SqlWriteT m Int64
- unsafeSqlAggregateFunction :: UnsafeSqlFunctionArgument a => Builder -> AggMode -> a -> [OrderByClause] -> SqlExpr (Value b)
Documentation
Aggregate mode
AggModeAll | ALL |
AggModeDistinct | DISTINCT |
arrayAggDistinct :: (PersistField a, PersistField [a]) => SqlExpr (Value a) -> SqlExpr (Value (Maybe [a])) Source #
(array_agg
) Concatenate distinct input values, including NULL
s, into
an array.
Since: 2.5.3
arrayAggWith :: AggMode -> SqlExpr (Value a) -> [OrderByClause] -> SqlExpr (Value (Maybe [a])) Source #
arrayRemove :: SqlExpr (Value [a]) -> SqlExpr (Value a) -> SqlExpr (Value [a]) Source #
(array_remove
) Remove all elements equal to the given value from the
array.
Since: 2.5.3
arrayRemoveNull :: SqlExpr (Value [Maybe a]) -> SqlExpr (Value [a]) Source #
Remove NULL
values from an array
:: SqlString s | |
=> SqlExpr (Value s) | Input values. |
-> SqlExpr (Value s) | Delimiter. |
-> SqlExpr (Value (Maybe s)) | Concatenation. |
(string_agg
) Concatenate input values separated by a
delimiter.
Since: 2.2.8
:: SqlString s | |
=> AggMode | Aggregate mode (ALL or DISTINCT) |
-> SqlExpr (Value s) | Input values. |
-> SqlExpr (Value s) | Delimiter. |
-> [OrderByClause] | ORDER BY clauses |
-> SqlExpr (Value (Maybe s)) | Concatenation. |
(string_agg
) Concatenate input values separated by a
delimiter.
maybeArray :: (PersistField a, PersistField [a]) => SqlExpr (Value (Maybe [a])) -> SqlExpr (Value [a]) Source #
Coalesce an array with an empty default value
chr :: SqlString s => SqlExpr (Value Int) -> SqlExpr (Value s) Source #
(chr
) Translate the given integer to a character. (Note the result will
depend on the character set of your database.)
Since: 2.2.11
random_ :: (PersistField a, Num a) => SqlExpr (Value a) Source #
(random()
) Split out into database specific modules
because MySQL uses `rand()`.
Since: 2.6.0
:: (MonadIO m, PersistEntity record, OnlyOneUniqueKey record, PersistRecordBackend record SqlBackend, IsPersistBackend (PersistEntityBackend record)) | |
=> record | new record to insert |
-> [SqlExpr (Update record)] | updates to perform if the record already exists |
-> ReaderT SqlBackend m (Entity record) | the record in the database after the operation |
:: (MonadIO m, PersistEntity record, IsPersistBackend (PersistEntityBackend record)) | |
=> Unique record | uniqueness constraint to find by |
-> record | new record to insert |
-> [SqlExpr (Update record)] | updates to perform if the record already exists |
-> ReaderT SqlBackend m (Entity record) | the record in the database after the operation |
insertSelectWithConflict Source #
:: (FinalResult a, KnowResult a ~ Unique val, MonadIO m, PersistEntity val) | |
=> a | Unique constructor or a unique, this is used just to get the name of the postgres constraint, the value(s) is(are) never used, so if you have a unique "MyUnique 0", "MyUnique undefined" would work as well. |
-> SqlQuery (SqlExpr (Insertion val)) | Insert query. |
-> (SqlExpr (Entity val) -> SqlExpr (Entity val) -> [SqlExpr (Update val)]) | A list of updates to be applied in case of the constraint being violated. The expression takes the current and excluded value to produce the updates. |
-> SqlWriteT m () |
Inserts into a table the results of a query similar to insertSelect
but allows
to update values that violate a constraint during insertions.
Example of usage:
share [ mkPersist sqlSettings , mkDeleteCascade sqlSettings , mkMigrate "migrate" ] [persistLowerCase| Bar num Int deriving Eq Show Foo num Int UniqueFoo num deriving Eq Show |] insertSelectWithConflict UniqueFoo -- (UniqueFoo undefined) or (UniqueFoo anyNumber) would also work (from $ b -> return $ Foo <# (b ^. BarNum) ) (current excluded -> [FooNum =. (current ^. FooNum) +. (excluded ^. FooNum)] )
Inserts to table Foo all Bar.num values and in case of conflict SomeFooUnique, the conflicting value is updated to the current plus the excluded.
Since: 3.1.3
insertSelectWithConflictCount :: forall a val m. (FinalResult a, KnowResult a ~ Unique val, MonadIO m, PersistEntity val) => a -> SqlQuery (SqlExpr (Insertion val)) -> (SqlExpr (Entity val) -> SqlExpr (Entity val) -> [SqlExpr (Update val)]) -> SqlWriteT m Int64 Source #
Same as insertSelectWithConflict
but returns the number of rows affected.
Since: 3.1.3
Internal
unsafeSqlAggregateFunction :: UnsafeSqlFunctionArgument a => Builder -> AggMode -> a -> [OrderByClause] -> SqlExpr (Value b) Source #
(Internal) Create a custom aggregate functions with aggregate mode
Do not use this function directly, instead define a new function and give
it a type (see unsafeSqlBinOp
)