persistent-2.14.0.1: Type-safe, multi-backend data serialization.
Safe HaskellNone
LanguageHaskell2010

Database.Persist.Compatible

Synopsis

Documentation

newtype Compatible b s Source #

A newtype wrapper for compatible backends, mainly useful for DerivingVia.

When writing a new backend that is BackendCompatible with an existing backend, instances for the new backend can be naturally defined in terms of the instances for the existing backend.

For example, if you decide to augment the SqlBackend with some additional features:

data BetterSqlBackend = BetterSqlBackend { sqlBackend :: SqlBackend, ... }

instance BackendCompatible SqlBackend BetterSqlBackend where
  projectBackend = sqlBackend

Then you can use DerivingVia to automatically get instances like:

deriving via (Compatible SqlBackend BetterSqlBackend) instance PersistStoreRead BetterSqlBackend
deriving via (Compatible SqlBackend BetterSqlBackend) instance PersistStoreWrite BetterSqlBackend
...

These instances will go through the compatible backend (in this case, SqlBackend) for all their queries.

These instances require that both backends have the same BaseBackend, but deriving HasPersistBackend will enforce that for you.

deriving via (Compatible SqlBackend BetterSqlBackend) instance HasPersistBackend BetterSqlBackend

Since: 2.12

Constructors

Compatible 

Fields

Instances

Instances details
(BackendCompatible b s, Bounded (BackendKey b)) => Bounded (BackendKey (Compatible b s)) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

(BackendCompatible b s, Enum (BackendKey b)) => Enum (BackendKey (Compatible b s)) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

(BackendCompatible b s, Eq (BackendKey b)) => Eq (BackendKey (Compatible b s)) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

(BackendCompatible b s, Integral (BackendKey b)) => Integral (BackendKey (Compatible b s)) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

(BackendCompatible b s, Num (BackendKey b)) => Num (BackendKey (Compatible b s)) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

(BackendCompatible b s, Ord (BackendKey b)) => Ord (BackendKey (Compatible b s)) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

(BackendCompatible b s, Read (BackendKey b)) => Read (BackendKey (Compatible b s)) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

(BackendCompatible b s, Real (BackendKey b)) => Real (BackendKey (Compatible b s)) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

(BackendCompatible b s, Show (BackendKey b)) => Show (BackendKey (Compatible b s)) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

(BackendCompatible b s, ToJSON (BackendKey b)) => ToJSON (BackendKey (Compatible b s)) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

(BackendCompatible b s, FromJSON (BackendKey b)) => FromJSON (BackendKey (Compatible b s)) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

(BackendCompatible b s, PersistField (BackendKey b)) => PersistField (BackendKey (Compatible b s)) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

(BackendCompatible b s, PersistFieldSql (BackendKey b)) => PersistFieldSql (BackendKey (Compatible b s)) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

(HasPersistBackend b, BackendCompatible b s, PersistStoreWrite b) => PersistStoreWrite (Compatible b s) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

Methods

insert :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s), SafeToInsert record) => record -> ReaderT (Compatible b s) m (Key record) Source #

insert_ :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s), SafeToInsert record) => record -> ReaderT (Compatible b s) m () Source #

insertMany :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s), SafeToInsert record) => [record] -> ReaderT (Compatible b s) m [Key record] Source #

insertMany_ :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s), SafeToInsert record) => [record] -> ReaderT (Compatible b s) m () Source #

insertEntityMany :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s)) => [Entity record] -> ReaderT (Compatible b s) m () Source #

insertKey :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s)) => Key record -> record -> ReaderT (Compatible b s) m () Source #

repsert :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s)) => Key record -> record -> ReaderT (Compatible b s) m () Source #

repsertMany :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s)) => [(Key record, record)] -> ReaderT (Compatible b s) m () Source #

replace :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s)) => Key record -> record -> ReaderT (Compatible b s) m () Source #

delete :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s)) => Key record -> ReaderT (Compatible b s) m () Source #

update :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s)) => Key record -> [Update record] -> ReaderT (Compatible b s) m () Source #

updateGet :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s)) => Key record -> [Update record] -> ReaderT (Compatible b s) m record Source #

(HasPersistBackend b, BackendCompatible b s, PersistStoreRead b) => PersistStoreRead (Compatible b s) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

Methods

get :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s)) => Key record -> ReaderT (Compatible b s) m (Maybe record) Source #

getMany :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s)) => [Key record] -> ReaderT (Compatible b s) m (Map (Key record) record) Source #

(BackendCompatible b s, PersistCore b) => PersistCore (Compatible b s) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

Associated Types

data BackendKey (Compatible b s) Source #

(BackendCompatible b s, HasPersistBackend b) => HasPersistBackend (Compatible b s) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

Associated Types

type BaseBackend (Compatible b s) Source #

(HasPersistBackend b, BackendCompatible b s, PersistUniqueWrite b) => PersistUniqueWrite (Compatible b s) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

Methods

deleteBy :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s)) => Unique record -> ReaderT (Compatible b s) m () Source #

insertUnique :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s), SafeToInsert record) => record -> ReaderT (Compatible b s) m (Maybe (Key record)) Source #

upsert :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s), OnlyOneUniqueKey record, SafeToInsert record) => record -> [Update record] -> ReaderT (Compatible b s) m (Entity record) Source #

upsertBy :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s), SafeToInsert record) => Unique record -> record -> [Update record] -> ReaderT (Compatible b s) m (Entity record) Source #

putMany :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s), SafeToInsert record) => [record] -> ReaderT (Compatible b s) m () Source #

(HasPersistBackend b, BackendCompatible b s, PersistUniqueRead b) => PersistUniqueRead (Compatible b s) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

Methods

getBy :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record (Compatible b s)) => Unique record -> ReaderT (Compatible b s) m (Maybe (Entity record)) Source #

(HasPersistBackend b, BackendCompatible b s, PersistQueryWrite b) => PersistQueryWrite (Compatible b s) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

Methods

updateWhere :: forall (m :: Type -> Type) record. (MonadIO m, PersistRecordBackend record (Compatible b s)) => [Filter record] -> [Update record] -> ReaderT (Compatible b s) m () Source #

deleteWhere :: forall (m :: Type -> Type) record. (MonadIO m, PersistRecordBackend record (Compatible b s)) => [Filter record] -> ReaderT (Compatible b s) m () Source #

(HasPersistBackend b, BackendCompatible b s, PersistQueryRead b) => PersistQueryRead (Compatible b s) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

Methods

selectSourceRes :: forall record (m1 :: Type -> Type) (m2 :: Type -> Type). (PersistRecordBackend record (Compatible b s), MonadIO m1, MonadIO m2) => [Filter record] -> [SelectOpt record] -> ReaderT (Compatible b s) m1 (Acquire (ConduitM () (Entity record) m2 ())) Source #

selectFirst :: forall (m :: Type -> Type) record. (MonadIO m, PersistRecordBackend record (Compatible b s)) => [Filter record] -> [SelectOpt record] -> ReaderT (Compatible b s) m (Maybe (Entity record)) Source #

selectKeysRes :: forall (m1 :: Type -> Type) (m2 :: Type -> Type) record. (MonadIO m1, MonadIO m2, PersistRecordBackend record (Compatible b s)) => [Filter record] -> [SelectOpt record] -> ReaderT (Compatible b s) m1 (Acquire (ConduitM () (Key record) m2 ())) Source #

count :: forall (m :: Type -> Type) record. (MonadIO m, PersistRecordBackend record (Compatible b s)) => [Filter record] -> ReaderT (Compatible b s) m Int Source #

exists :: forall (m :: Type -> Type) record. (MonadIO m, PersistRecordBackend record (Compatible b s)) => [Filter record] -> ReaderT (Compatible b s) m Bool Source #

newtype BackendKey (Compatible b s) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

type BaseBackend (Compatible b s) Source # 
Instance details

Defined in Database.Persist.Compatible.Types

makeCompatibleInstances :: Q Type -> Q [Dec] Source #

Gives a bunch of useful instance declarations for a backend based on its compatibility with another backend, using Compatible.

The argument should be a type of the form forall v1 ... vn. Compatible b s (Quantification is optional, but supported because TH won't let you have unbound type variables in a type splice). The instance is produced for s based on the instance defined for b, which is constrained in the instance head to exist.

v1 ... vn are implicitly quantified in the instance, which is derived via Compatible b s.

Since: 2.12

makeCompatibleKeyInstances :: Q Type -> Q [Dec] Source #

Gives a bunch of useful instance declarations for a backend key based on its compatibility with another backend & key, using Compatible.

The argument should be a type of the form forall v1 ... vn. Compatible b s (Quantification is optional, but supported because TH won't let you have unbound type variables in a type splice). The instance is produced for BackendKey s based on the instance defined for BackendKey b, which is constrained in the instance head to exist.

v1 ... vn are implicitly quantified in the instance, which is derived via BackendKey (Compatible b s).

Since: 2.12