Safe Haskell | None |
---|---|
Language | Haskell2010 |
Yesod.Persist
Documentation
module Yesod.Persist.Core
class (PersistField (Key record), ToJSON (Key record), FromJSON (Key record), Show (Key record), Read (Key record), Eq (Key record), Ord (Key record)) => PersistEntity record where #
Minimal complete definition
keyToValues, keyFromValues, persistIdField, entityDef, persistFieldDef, toPersistFields, fromPersistValues, tabulateEntityA, persistUniqueKeys, persistUniqueToFieldNames, persistUniqueToValues, fieldLens
Methods
keyToValues :: Key record -> [PersistValue] #
keyFromValues :: [PersistValue] -> Either Text (Key record) #
persistIdField :: EntityField record (Key record) #
entityDef :: proxy record -> EntityDef #
persistFieldDef :: EntityField record typ -> FieldDef #
toPersistFields :: record -> [PersistValue] #
fromPersistValues :: [PersistValue] -> Either Text record #
tabulateEntityA :: Applicative f => (forall a. EntityField record a -> f a) -> f (Entity record) #
persistUniqueKeys :: record -> [Unique record] #
persistUniqueToFieldNames :: Unique record -> NonEmpty (FieldNameHS, FieldNameDB) #
persistUniqueToValues :: Unique record -> [PersistValue] #
fieldLens :: EntityField record field -> forall (f :: Type -> Type). Functor f => (field -> f field) -> Entity record -> f (Entity record) #
keyFromRecordM :: Maybe (record -> Key record) #
class PersistConfig c where #
Minimal complete definition
Associated Types
type PersistConfigBackend c :: (Type -> Type) -> Type -> Type #
type PersistConfigPool c #
Methods
loadConfig :: Value -> Parser c #
createPoolConfig :: c -> IO (PersistConfigPool c) #
runPool :: MonadUnliftIO m => c -> PersistConfigBackend c m a -> PersistConfigPool c -> m a #
Instances
(PersistConfig c1, PersistConfig c2, PersistConfigPool c1 ~ PersistConfigPool c2, PersistConfigBackend c1 ~ PersistConfigBackend c2) => PersistConfig (Either c1 c2) | |||||||||
Defined in Database.Persist.Class.PersistConfig Associated Types
Methods loadConfig :: Value -> Parser (Either c1 c2) # applyEnv :: Either c1 c2 -> IO (Either c1 c2) # createPoolConfig :: Either c1 c2 -> IO (PersistConfigPool (Either c1 c2)) # runPool :: MonadUnliftIO m => Either c1 c2 -> PersistConfigBackend (Either c1 c2) m a -> PersistConfigPool (Either c1 c2) -> m a # |
type family PersistConfigPool c #
Instances
type PersistConfigPool (Either c1 c2) | |
Defined in Database.Persist.Class.PersistConfig |
type family PersistConfigBackend c :: (Type -> Type) -> Type -> Type #
Instances
type PersistConfigBackend (Either c1 c2) | |
Defined in Database.Persist.Class.PersistConfig |
class HasPersistBackend backend where #
Associated Types
type BaseBackend backend #
Methods
persistBackend :: backend -> BaseBackend backend #
Instances
HasPersistBackend SqlReadBackend | |||||
Defined in Database.Persist.Sql.Types.Internal Associated Types
Methods persistBackend :: SqlReadBackend -> BaseBackend SqlReadBackend # | |||||
HasPersistBackend SqlWriteBackend | |||||
Defined in Database.Persist.Sql.Types.Internal Associated Types
Methods persistBackend :: SqlWriteBackend -> BaseBackend SqlWriteBackend # | |||||
HasPersistBackend SqlBackend | |||||
Defined in Database.Persist.SqlBackend.Internal Associated Types
Methods persistBackend :: SqlBackend -> BaseBackend SqlBackend # |
class (Show (BackendKey backend), Read (BackendKey backend), Eq (BackendKey backend), Ord (BackendKey backend), PersistCore backend, PersistField (BackendKey backend), ToJSON (BackendKey backend), FromJSON (BackendKey backend)) => PersistStoreRead backend where #
Minimal complete definition
Methods
get :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend) => Key record -> ReaderT backend m (Maybe record) #
getMany :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend) => [Key record] -> ReaderT backend m (Map (Key record) record) #
type PersistRecordBackend record backend = (PersistEntity record, PersistEntityBackend record ~ BaseBackend backend) #
class PersistStoreRead backend => PersistUniqueRead backend where #
Minimal complete definition
Methods
getBy :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend) => Unique record -> ReaderT backend m (Maybe (Entity record)) #
existsBy :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend) => Unique record -> ReaderT backend m Bool #
Instances
(Generic (Key record), Generic record) => Generic (Entity record) | |||||
Defined in Database.Persist.Class.PersistEntity Associated Types
| |||||
(Read (Key record), Read record) => Read (Entity record) | |||||
Defined in Database.Persist.Class.PersistEntity | |||||
(Show (Key record), Show record) => Show (Entity record) | |||||
(Eq (Key record), Eq record) => Eq (Entity record) | |||||
(Ord (Key record), Ord record) => Ord (Entity record) | |||||
Defined in Database.Persist.Class.PersistEntity | |||||
(TypeError (EntityErrorMessage a) :: Constraint) => SafeToInsert (Entity a) | |||||
Defined in Database.Persist.Class.PersistEntity | |||||
(PersistEntity record, PersistField record, PersistField (Key record)) => PersistField (Entity record) | |||||
Defined in Database.Persist.Class.PersistEntity Methods toPersistValue :: Entity record -> PersistValue # fromPersistValue :: PersistValue -> Either Text (Entity record) # | |||||
type Rep (Entity record) | |||||
Defined in Database.Persist.Class.PersistEntity type Rep (Entity record) = D1 ('MetaData "Entity" "Database.Persist.Class.PersistEntity" "persistent-2.14.6.3-9eigWuCCw7EBFqLkPQMMa9" 'False) (C1 ('MetaCons "Entity" 'PrefixI 'True) (S1 ('MetaSel ('Just "entityKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Key record)) :*: S1 ('MetaSel ('Just "entityVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 record))) |
class (PersistUniqueRead backend, PersistStoreWrite backend) => PersistUniqueWrite backend where #
Minimal complete definition
Methods
deleteBy :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend) => Unique record -> ReaderT backend m () #
insertUnique :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => record -> ReaderT backend m (Maybe (Key record)) #
insertUnique_ :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => record -> ReaderT backend m (Maybe ()) #
upsert :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend, OnlyOneUniqueKey record, SafeToInsert record) => record -> [Update record] -> ReaderT backend m (Entity record) #
upsertBy :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => Unique record -> record -> [Update record] -> ReaderT backend m (Entity record) #
putMany :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => [record] -> ReaderT backend m () #
class SafeToInsert a #
Instances
(TypeError (EntityErrorMessage a) :: Constraint) => SafeToInsert (Entity a) | |
Defined in Database.Persist.Class.PersistEntity | |
(TypeError (FunctionErrorMessage a b) :: Constraint) => SafeToInsert (a -> b) | |
Defined in Database.Persist.Class.PersistEntity |
checkUnique :: forall record backend (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend, PersistUniqueRead backend) => record -> ReaderT backend m (Maybe (Unique record)) #
newtype FieldNameHS #
Constructors
FieldNameHS | |
Fields
|
Instances
Read FieldNameHS | |
Defined in Database.Persist.Names Methods readsPrec :: Int -> ReadS FieldNameHS readList :: ReadS [FieldNameHS] readPrec :: ReadPrec FieldNameHS readListPrec :: ReadPrec [FieldNameHS] | |
Show FieldNameHS | |
Defined in Database.Persist.Names Methods showsPrec :: Int -> FieldNameHS -> ShowS show :: FieldNameHS -> String showList :: [FieldNameHS] -> ShowS | |
Eq FieldNameHS | |
Defined in Database.Persist.Names | |
Ord FieldNameHS | |
Defined in Database.Persist.Names Methods compare :: FieldNameHS -> FieldNameHS -> Ordering (<) :: FieldNameHS -> FieldNameHS -> Bool (<=) :: FieldNameHS -> FieldNameHS -> Bool (>) :: FieldNameHS -> FieldNameHS -> Bool (>=) :: FieldNameHS -> FieldNameHS -> Bool max :: FieldNameHS -> FieldNameHS -> FieldNameHS min :: FieldNameHS -> FieldNameHS -> FieldNameHS | |
Lift FieldNameHS | |
Defined in Database.Persist.Names Methods lift :: Quote m => FieldNameHS -> m Exp liftTyped :: forall (m :: Type -> Type). Quote m => FieldNameHS -> Code m FieldNameHS |
class (Show (BackendKey backend), Read (BackendKey backend), Eq (BackendKey backend), Ord (BackendKey backend), PersistStoreRead backend, PersistField (BackendKey backend), ToJSON (BackendKey backend), FromJSON (BackendKey backend)) => PersistStoreWrite backend where #
Methods
insert :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => record -> ReaderT backend m (Key record) #
insert_ :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => record -> ReaderT backend m () #
insertMany :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => [record] -> ReaderT backend m [Key record] #
insertMany_ :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => [record] -> ReaderT backend m () #
insertEntityMany :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend) => [Entity record] -> ReaderT backend m () #
insertKey :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend) => Key record -> record -> ReaderT backend m () #
repsert :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend) => Key record -> record -> ReaderT backend m () #
repsertMany :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend) => [(Key record, record)] -> ReaderT backend m () #
replace :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend) => Key record -> record -> ReaderT backend m () #
delete :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend) => Key record -> ReaderT backend m () #
update :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend) => Key record -> [Update record] -> ReaderT backend m () #
updateGet :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend) => Key record -> [Update record] -> ReaderT backend m record #
data PersistFilter #
Instances
Read PersistFilter | |
Defined in Database.Persist.Types.Base Methods readsPrec :: Int -> ReadS PersistFilter readList :: ReadS [PersistFilter] readPrec :: ReadPrec PersistFilter readListPrec :: ReadPrec [PersistFilter] | |
Show PersistFilter | |
Defined in Database.Persist.Types.Base Methods showsPrec :: Int -> PersistFilter -> ShowS show :: PersistFilter -> String showList :: [PersistFilter] -> ShowS | |
Lift PersistFilter | |
Defined in Database.Persist.Types.Base Methods lift :: Quote m => PersistFilter -> m Exp liftTyped :: forall (m :: Type -> Type). Quote m => PersistFilter -> Code m PersistFilter |
type PersistQuery a = PersistQueryWrite a #
type PersistStore a = PersistStoreWrite a #
type PersistUnique a = PersistUniqueWrite a #
Constructors
Asc (EntityField record typ) | |
Desc (EntityField record typ) | |
OffsetBy Int | |
LimitTo Int |
Constructors
PersistField typ => Filter | |
Fields
| |
FilterAnd [Filter record] | |
FilterOr [Filter record] | |
BackendFilter (BackendSpecificFilter (PersistEntityBackend record) record) |
type family BackendSpecificFilter backend record #
type family BackendSpecificUpdate backend record #
data PersistUpdate #
Instances
Read PersistUpdate | |
Defined in Database.Persist.Types.Base Methods readsPrec :: Int -> ReadS PersistUpdate readList :: ReadS [PersistUpdate] readPrec :: ReadPrec PersistUpdate readListPrec :: ReadPrec [PersistUpdate] | |
Show PersistUpdate | |
Defined in Database.Persist.Types.Base Methods showsPrec :: Int -> PersistUpdate -> ShowS show :: PersistUpdate -> String showList :: [PersistUpdate] -> ShowS | |
Lift PersistUpdate | |
Defined in Database.Persist.Types.Base Methods lift :: Quote m => PersistUpdate -> m Exp liftTyped :: forall (m :: Type -> Type). Quote m => PersistUpdate -> Code m PersistUpdate |
Constructors
PersistField typ => Update | |
Fields
| |
BackendUpdate (BackendSpecificUpdate (PersistEntityBackend record) record) |
data family EntityField record :: Type -> Type #
Instances
SymbolToField sym rec typ => IsLabel sym (EntityField rec typ) | |
Defined in Database.Persist.Class.PersistEntity Methods fromLabel :: EntityField rec typ |
data FilterValue typ where #
Constructors
FilterValue :: forall typ. typ -> FilterValue typ | |
FilterValues :: forall typ. [typ] -> FilterValue typ | |
UnsafeValue :: forall a typ. PersistField a => a -> FilterValue typ |
type family PersistEntityBackend record #
class SymbolToField (sym :: Symbol) rec typ | sym rec -> typ where #
Methods
symbolToField :: EntityField rec typ #
entityIdFromJSON :: (PersistEntity record, FromJSON record) => Value -> Parser (Entity record) #
entityIdToJSON :: (PersistEntity record, ToJSON record) => Entity record -> Value #
entityValues :: PersistEntity record => Entity record -> [PersistValue] #
fromPersistValueJSON :: FromJSON a => PersistValue -> Either Text a #
keyValueEntityFromJSON :: (PersistEntity record, FromJSON record) => Value -> Parser (Entity record) #
keyValueEntityToJSON :: (PersistEntity record, ToJSON record) => Entity record -> Value #
tabulateEntity :: PersistEntity record => (forall a. EntityField record a -> a) -> Entity record #
toPersistValueJSON :: ToJSON a => a -> PersistValue #
newtype OverflowNatural #
Constructors
OverflowNatural | |
Fields
|
Instances
class PersistField a where #
Instances
getPersistMap :: PersistValue -> Either Text [(Text, PersistValue)] #
class (PersistCore backend, PersistStoreRead backend) => PersistQueryRead backend where #
Minimal complete definition
Methods
selectSourceRes :: forall record (m1 :: Type -> Type) (m2 :: Type -> Type). (PersistRecordBackend record backend, MonadIO m1, MonadIO m2) => [Filter record] -> [SelectOpt record] -> ReaderT backend m1 (Acquire (ConduitM () (Entity record) m2 ())) #
selectFirst :: forall (m :: Type -> Type) record. (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m (Maybe (Entity record)) #
selectKeysRes :: forall (m1 :: Type -> Type) (m2 :: Type -> Type) record. (MonadIO m1, MonadIO m2, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m1 (Acquire (ConduitM () (Key record) m2 ())) #
count :: forall (m :: Type -> Type) record. (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> ReaderT backend m Int #
exists :: forall (m :: Type -> Type) record. (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> ReaderT backend m Bool #
class (PersistQueryRead backend, PersistStoreWrite backend) => PersistQueryWrite backend where #
Methods
updateWhere :: forall (m :: Type -> Type) record. (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> [Update record] -> ReaderT backend m () #
deleteWhere :: forall (m :: Type -> Type) record. (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> ReaderT backend m () #
selectKeys :: forall record backend (m :: Type -> Type). (PersistQueryRead backend, MonadResource m, PersistRecordBackend record backend, MonadReader backend m) => [Filter record] -> [SelectOpt record] -> ConduitM () (Key record) m () #
selectKeysList :: forall record backend (m :: Type -> Type). (MonadIO m, PersistQueryRead backend, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m [Key record] #
selectList :: forall record backend (m :: Type -> Type). (MonadIO m, PersistQueryRead backend, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m [Entity record] #
selectSource :: forall record backend (m :: Type -> Type). (PersistQueryRead backend, MonadResource m, PersistRecordBackend record backend, MonadReader backend m) => [Filter record] -> [SelectOpt record] -> ConduitM () (Entity record) m () #
class BackendCompatible sup sub where #
Methods
projectBackend :: sub -> sup #
class PersistCore backend #
Associated Types
data BackendKey backend #
data family BackendKey backend #
Instances
newtype BackendKey SqlReadBackend | |
Defined in Database.Persist.Sql.Orphan.PersistStore | |
newtype BackendKey SqlWriteBackend | |
Defined in Database.Persist.Sql.Orphan.PersistStore | |
newtype BackendKey SqlBackend | |
Defined in Database.Persist.Sql.Orphan.PersistStore | |
type Rep (BackendKey SqlReadBackend) | |
Defined in Database.Persist.Sql.Orphan.PersistStore type Rep (BackendKey SqlReadBackend) = D1 ('MetaData "BackendKey" "Database.Persist.Sql.Orphan.PersistStore" "persistent-2.14.6.3-9eigWuCCw7EBFqLkPQMMa9" 'True) (C1 ('MetaCons "SqlReadBackendKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSqlReadBackendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64))) | |
type Rep (BackendKey SqlWriteBackend) | |
Defined in Database.Persist.Sql.Orphan.PersistStore type Rep (BackendKey SqlWriteBackend) = D1 ('MetaData "BackendKey" "Database.Persist.Sql.Orphan.PersistStore" "persistent-2.14.6.3-9eigWuCCw7EBFqLkPQMMa9" 'True) (C1 ('MetaCons "SqlWriteBackendKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSqlWriteBackendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64))) | |
type Rep (BackendKey SqlBackend) | |
Defined in Database.Persist.Sql.Orphan.PersistStore type Rep (BackendKey SqlBackend) = D1 ('MetaData "BackendKey" "Database.Persist.Sql.Orphan.PersistStore" "persistent-2.14.6.3-9eigWuCCw7EBFqLkPQMMa9" 'True) (C1 ('MetaCons "SqlBackendKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSqlBackendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64))) |
type family BaseBackend backend #
Instances
type BaseBackend SqlReadBackend | |
Defined in Database.Persist.Sql.Types.Internal type BaseBackend SqlReadBackend = SqlBackend | |
type BaseBackend SqlWriteBackend | |
Defined in Database.Persist.Sql.Types.Internal type BaseBackend SqlWriteBackend = SqlBackend | |
type BaseBackend SqlBackend | |
Defined in Database.Persist.SqlBackend.Internal type BaseBackend SqlBackend = SqlBackend |
class HasPersistBackend backend => IsPersistBackend backend #
Minimal complete definition
mkPersistBackend
Instances
IsPersistBackend SqlReadBackend | |
Defined in Database.Persist.Sql.Types.Internal Methods mkPersistBackend :: BaseBackend SqlReadBackend -> SqlReadBackend | |
IsPersistBackend SqlWriteBackend | |
Defined in Database.Persist.Sql.Types.Internal Methods mkPersistBackend :: BaseBackend SqlWriteBackend -> SqlWriteBackend | |
IsPersistBackend SqlBackend | |
Defined in Database.Persist.SqlBackend.Internal Methods mkPersistBackend :: BaseBackend SqlBackend -> SqlBackend |
class (PersistEntity record, PersistEntityBackend record ~ backend, PersistCore backend) => ToBackendKey backend record where #
Methods
toBackendKey :: Key record -> BackendKey backend #
fromBackendKey :: BackendKey backend -> Key record #
belongsTo :: forall ent1 ent2 backend (m :: Type -> Type). (PersistStoreRead backend, PersistEntity ent1, PersistRecordBackend ent2 backend, MonadIO m) => (ent1 -> Maybe (Key ent2)) -> ent1 -> ReaderT backend m (Maybe ent2) #
belongsToJust :: forall ent1 ent2 backend (m :: Type -> Type). (PersistStoreRead backend, PersistEntity ent1, PersistRecordBackend ent2 backend, MonadIO m) => (ent1 -> Key ent2) -> ent1 -> ReaderT backend m ent2 #
getEntity :: forall e backend (m :: Type -> Type). (PersistStoreRead backend, PersistRecordBackend e backend, MonadIO m) => Key e -> ReaderT backend m (Maybe (Entity e)) #
getJust :: forall record backend (m :: Type -> Type). (PersistStoreRead backend, PersistRecordBackend record backend, MonadIO m) => Key record -> ReaderT backend m record #
getJustEntity :: forall record backend (m :: Type -> Type). (PersistEntityBackend record ~ BaseBackend backend, MonadIO m, PersistEntity record, PersistStoreRead backend) => Key record -> ReaderT backend m (Entity record) #
insertEntity :: forall e backend (m :: Type -> Type). (PersistStoreWrite backend, PersistRecordBackend e backend, SafeToInsert e, MonadIO m, HasCallStack) => e -> ReaderT backend m (Entity e) #
insertRecord :: forall record backend (m :: Type -> Type). (PersistEntityBackend record ~ BaseBackend backend, PersistEntity record, MonadIO m, PersistStoreWrite backend, SafeToInsert record, HasCallStack) => record -> ReaderT backend m record #
liftPersist :: (MonadIO m, MonadReader backend m) => ReaderT backend IO b -> m b #
withBaseBackend :: forall backend (m :: Type -> Type) a. HasPersistBackend backend => ReaderT (BaseBackend backend) m a -> ReaderT backend m a #
withCompatibleBackend :: forall sup sub (m :: Type -> Type) a. BackendCompatible sup sub => ReaderT sup m a -> ReaderT sub m a #
class PersistEntity record => AtLeastOneUniqueKey record where #
Methods
requireUniquesP :: record -> NonEmpty (Unique record) #
type MultipleUniqueKeysError ty = ((('Text "The entity " ':<>: 'ShowType ty) ':<>: 'Text " has multiple unique keys.") ':$$: ('Text "The function you are trying to call requires only a single " ':<>: 'Text "unique key.")) ':$$: (('Text "There is probably a variant of the function with 'By' " ':<>: 'Text "appended that will allow you to select a unique key ") ':<>: 'Text "for the operation.") #
type NoUniqueKeysError ty = (('Text "The entity " ':<>: 'ShowType ty) ':<>: 'Text " does not have any unique keys.") ':$$: ('Text "The function you are trying to call requires a unique key " ':<>: 'Text "to be defined on the entity.") #
class PersistEntity record => OnlyOneUniqueKey record where #
Methods
onlyUniqueP :: record -> Unique record #
checkUniqueUpdateable :: forall record backend (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend, PersistUniqueRead backend) => Entity record -> ReaderT backend m (Maybe (Unique record)) #
getByValue :: forall record (m :: Type -> Type) backend. (MonadIO m, PersistUniqueRead backend, PersistRecordBackend record backend, AtLeastOneUniqueKey record) => record -> ReaderT backend m (Maybe (Entity record)) #
insertBy :: forall record backend (m :: Type -> Type). (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend record backend, AtLeastOneUniqueKey record, SafeToInsert record) => record -> ReaderT backend m (Either (Entity record) (Key record)) #
insertUniqueEntity :: forall record backend (m :: Type -> Type). (MonadIO m, PersistRecordBackend record backend, PersistUniqueWrite backend, SafeToInsert record) => record -> ReaderT backend m (Maybe (Entity record)) #
onlyOneUniqueDef :: (OnlyOneUniqueKey record, Monad proxy) => proxy record -> UniqueDef #
onlyUnique :: forall record backend (m :: Type -> Type). (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend record backend, OnlyOneUniqueKey record) => record -> ReaderT backend m (Unique record) #
replaceUnique :: forall record backend (m :: Type -> Type). (MonadIO m, Eq (Unique record), PersistRecordBackend record backend, PersistUniqueWrite backend) => Key record -> record -> ReaderT backend m (Maybe (Unique record)) #
getEntityComments :: EntityDef -> Maybe Text #
getEntityExtra :: EntityDef -> Map Text [[Text]] #
getEntityFields :: EntityDef -> [FieldDef] #
getEntityFieldsDatabase :: EntityDef -> [FieldDef] #
getEntityForeignDefs :: EntityDef -> [ForeignDef] #
getEntityId :: EntityDef -> EntityIdDef #
getEntityIdField :: EntityDef -> Maybe FieldDef #
getEntityKeyFields :: EntityDef -> NonEmpty FieldDef #
getEntityUniques :: EntityDef -> [UniqueDef] #
isEntitySum :: EntityDef -> Bool #
setEntityDBName :: EntityNameDB -> EntityDef -> EntityDef #
setEntityId :: FieldDef -> EntityDef -> EntityDef #
setEntityIdDef :: EntityIdDef -> EntityDef -> EntityDef #
addFieldAttr :: FieldAttr -> FieldDef -> FieldDef #
isFieldMaybe :: FieldDef -> Bool #
isFieldNullable :: FieldDef -> IsNullable #
setFieldAttrs :: [FieldAttr] -> FieldDef -> FieldDef #
newtype ConstraintNameDB #
Constructors
ConstraintNameDB | |
Fields
|
Instances
newtype ConstraintNameHS #
Constructors
ConstraintNameHS | |
Fields
|
Instances
class DatabaseName a where #
Methods
escapeWith :: (Text -> str) -> a -> str #
Instances
DatabaseName ConstraintNameDB | |
Defined in Database.Persist.Names Methods escapeWith :: (Text -> str) -> ConstraintNameDB -> str # | |
DatabaseName EntityNameDB | |
Defined in Database.Persist.Names Methods escapeWith :: (Text -> str) -> EntityNameDB -> str # | |
DatabaseName FieldNameDB | |
Defined in Database.Persist.Names Methods escapeWith :: (Text -> str) -> FieldNameDB -> str # |
newtype EntityNameDB #
Constructors
EntityNameDB | |
Fields
|
Instances
newtype EntityNameHS #
Constructors
EntityNameHS | |
Fields
|
Instances
Read EntityNameHS | |
Defined in Database.Persist.Names Methods readsPrec :: Int -> ReadS EntityNameHS readList :: ReadS [EntityNameHS] readPrec :: ReadPrec EntityNameHS readListPrec :: ReadPrec [EntityNameHS] | |
Show EntityNameHS | |
Defined in Database.Persist.Names Methods showsPrec :: Int -> EntityNameHS -> ShowS show :: EntityNameHS -> String showList :: [EntityNameHS] -> ShowS | |
Eq EntityNameHS | |
Defined in Database.Persist.Names | |
Ord EntityNameHS | |
Defined in Database.Persist.Names Methods compare :: EntityNameHS -> EntityNameHS -> Ordering (<) :: EntityNameHS -> EntityNameHS -> Bool (<=) :: EntityNameHS -> EntityNameHS -> Bool (>) :: EntityNameHS -> EntityNameHS -> Bool (>=) :: EntityNameHS -> EntityNameHS -> Bool max :: EntityNameHS -> EntityNameHS -> EntityNameHS min :: EntityNameHS -> EntityNameHS -> EntityNameHS | |
Lift EntityNameHS | |
Defined in Database.Persist.Names Methods lift :: Quote m => EntityNameHS -> m Exp liftTyped :: forall (m :: Type -> Type). Quote m => EntityNameHS -> Code m EntityNameHS |
newtype FieldNameDB #
Constructors
FieldNameDB | |
Fields
|
Instances
data LiteralType #
Constructors
Escaped | |
Unescaped | |
DbSpecific |
Instances
Read LiteralType | |
Defined in Database.Persist.PersistValue Methods readsPrec :: Int -> ReadS LiteralType readList :: ReadS [LiteralType] readPrec :: ReadPrec LiteralType readListPrec :: ReadPrec [LiteralType] | |
Show LiteralType | |
Defined in Database.Persist.PersistValue Methods showsPrec :: Int -> LiteralType -> ShowS show :: LiteralType -> String showList :: [LiteralType] -> ShowS | |
Eq LiteralType | |
Defined in Database.Persist.PersistValue | |
Ord LiteralType | |
Defined in Database.Persist.PersistValue Methods compare :: LiteralType -> LiteralType -> Ordering (<) :: LiteralType -> LiteralType -> Bool (<=) :: LiteralType -> LiteralType -> Bool (>) :: LiteralType -> LiteralType -> Bool (>=) :: LiteralType -> LiteralType -> Bool max :: LiteralType -> LiteralType -> LiteralType min :: LiteralType -> LiteralType -> LiteralType |
data PersistValue #
Constructors
PersistText Text | |
PersistByteString ByteString | |
PersistInt64 Int64 | |
PersistDouble Double | |
PersistRational Rational | |
PersistBool Bool | |
PersistDay Day | |
PersistTimeOfDay TimeOfDay | |
PersistUTCTime UTCTime | |
PersistNull | |
PersistList [PersistValue] | |
PersistMap [(Text, PersistValue)] | |
PersistObjectId ByteString | |
PersistArray [PersistValue] | |
PersistLiteral_ LiteralType ByteString |
Bundled Patterns
pattern PersistDbSpecific :: ByteString -> PersistValue | |
pattern PersistLiteral :: ByteString -> PersistValue | |
pattern PersistLiteralEscaped :: ByteString -> PersistValue |
Instances
fromPersistValueText :: PersistValue -> Either Text Text #
Instances
Bounded Checkmark | |
Defined in Database.Persist.Types.Base | |
Enum Checkmark | |
Defined in Database.Persist.Types.Base | |
Read Checkmark | |
Defined in Database.Persist.Types.Base | |
Show Checkmark | |
Eq Checkmark | |
Ord Checkmark | |
Defined in Database.Persist.Types.Base | |
FromHttpApiData Checkmark | |
Defined in Database.Persist.Types.Base Methods parseUrlPiece :: Text -> Either Text Checkmark parseHeader :: ByteString -> Either Text Checkmark parseQueryParam :: Text -> Either Text Checkmark | |
ToHttpApiData Checkmark | |
Defined in Database.Persist.Types.Base Methods toUrlPiece :: Checkmark -> Text toEncodedUrlPiece :: Checkmark -> Builder toHeader :: Checkmark -> ByteString toQueryParam :: Checkmark -> Text toEncodedQueryParam :: Checkmark -> Builder | |
PathPiece Checkmark | |
Defined in Database.Persist.Types.Base | |
PersistField Checkmark | |
Defined in Database.Persist.Class.PersistField Methods toPersistValue :: Checkmark -> PersistValue # fromPersistValue :: PersistValue -> Either Text Checkmark # |
data WhyNullable #
Constructors
ByMaybeAttr | |
ByNullableAttr |
Instances
Show WhyNullable | |
Defined in Database.Persist.Types.Base Methods showsPrec :: Int -> WhyNullable -> ShowS show :: WhyNullable -> String showList :: [WhyNullable] -> ShowS | |
Eq WhyNullable | |
Defined in Database.Persist.Types.Base |
data CascadeAction #
Constructors
Cascade | |
Restrict | |
SetNull | |
SetDefault |
Instances
data CompositeDef #
Constructors
CompositeDef | |
Fields
|
Instances
data EmbedEntityDef #
Constructors
EmbedEntityDef | |
Fields |
Instances
data EmbedFieldDef #
Constructors
EmbedFieldDef | |
Fields
|
Instances
data ReferenceDef #
Constructors
NoReference | |
ForeignRef !EntityNameHS | |
EmbedRef EntityNameHS | |
SelfReference |
Instances
Instances
Read EntityDef | |
Defined in Database.Persist.Types.Base | |
Show EntityDef | |
Eq EntityDef | |
Ord EntityDef | |
Defined in Database.Persist.Types.Base | |
Lift EntityDef | |
data EntityIdDef #
Constructors
EntityIdField !FieldDef | |
EntityIdNaturalKey !CompositeDef |
Instances
Read EntityIdDef | |
Defined in Database.Persist.Types.Base Methods readsPrec :: Int -> ReadS EntityIdDef readList :: ReadS [EntityIdDef] readPrec :: ReadPrec EntityIdDef readListPrec :: ReadPrec [EntityIdDef] | |
Show EntityIdDef | |
Defined in Database.Persist.Types.Base Methods showsPrec :: Int -> EntityIdDef -> ShowS show :: EntityIdDef -> String showList :: [EntityIdDef] -> ShowS | |
Eq EntityIdDef | |
Defined in Database.Persist.Types.Base | |
Ord EntityIdDef | |
Defined in Database.Persist.Types.Base Methods compare :: EntityIdDef -> EntityIdDef -> Ordering (<) :: EntityIdDef -> EntityIdDef -> Bool (<=) :: EntityIdDef -> EntityIdDef -> Bool (>) :: EntityIdDef -> EntityIdDef -> Bool (>=) :: EntityIdDef -> EntityIdDef -> Bool max :: EntityIdDef -> EntityIdDef -> EntityIdDef min :: EntityIdDef -> EntityIdDef -> EntityIdDef | |
Lift EntityIdDef | |
Defined in Database.Persist.Types.Base Methods lift :: Quote m => EntityIdDef -> m Exp liftTyped :: forall (m :: Type -> Type). Quote m => EntityIdDef -> Code m EntityIdDef |
Constructors
FTTypeCon (Maybe Text) Text | |
FTLit FieldTypeLit | |
FTTypePromoted Text | |
FTApp FieldType FieldType | |
FTList FieldType |
Instances
Read FieldType | |
Defined in Database.Persist.Types.Base | |
Show FieldType | |
Eq FieldType | |
Ord FieldType | |
Defined in Database.Persist.Types.Base | |
Lift FieldType | |
Constructors
Instances
Read FieldAttr | |
Defined in Database.Persist.Types.Base | |
Show FieldAttr | |
Eq FieldAttr | |
Ord FieldAttr | |
Defined in Database.Persist.Types.Base | |
Lift FieldAttr | |
data FieldCascade #
Constructors
FieldCascade | |
Fields
|
Instances
Constructors
FieldDef | |
Fields
|
Instances
Read FieldDef | |
Defined in Database.Persist.Types.Base | |
Show FieldDef | |
Eq FieldDef | |
Ord FieldDef | |
Defined in Database.Persist.Types.Base | |
Lift FieldDef | |
data ForeignDef #
Constructors
ForeignDef | |
Fields
|
Instances
Read ForeignDef | |
Defined in Database.Persist.Types.Base Methods readsPrec :: Int -> ReadS ForeignDef readList :: ReadS [ForeignDef] readPrec :: ReadPrec ForeignDef readListPrec :: ReadPrec [ForeignDef] | |
Show ForeignDef | |
Defined in Database.Persist.Types.Base Methods showsPrec :: Int -> ForeignDef -> ShowS show :: ForeignDef -> String showList :: [ForeignDef] -> ShowS | |
Eq ForeignDef | |
Defined in Database.Persist.Types.Base | |
Ord ForeignDef | |
Defined in Database.Persist.Types.Base Methods compare :: ForeignDef -> ForeignDef -> Ordering (<) :: ForeignDef -> ForeignDef -> Bool (<=) :: ForeignDef -> ForeignDef -> Bool (>) :: ForeignDef -> ForeignDef -> Bool (>=) :: ForeignDef -> ForeignDef -> Bool max :: ForeignDef -> ForeignDef -> ForeignDef min :: ForeignDef -> ForeignDef -> ForeignDef | |
Lift ForeignDef | |
Defined in Database.Persist.Types.Base Methods lift :: Quote m => ForeignDef -> m Exp liftTyped :: forall (m :: Type -> Type). Quote m => ForeignDef -> Code m ForeignDef |
type ForeignFieldDef = (FieldNameHS, FieldNameDB) #
data IsNullable #
Constructors
Nullable !WhyNullable | |
NotNullable |
Instances
Show IsNullable | |
Defined in Database.Persist.Types.Base Methods showsPrec :: Int -> IsNullable -> ShowS show :: IsNullable -> String showList :: [IsNullable] -> ShowS | |
Eq IsNullable | |
Defined in Database.Persist.Types.Base |
data UpdateException #
Constructors
KeyNotFound String | |
UpsertError String |
Instances
Exception UpdateException | |
Defined in Database.Persist.Types.Base Methods toException :: UpdateException -> SomeException fromException :: SomeException -> Maybe UpdateException displayException :: UpdateException -> String | |
Show UpdateException | |
Defined in Database.Persist.Types.Base Methods showsPrec :: Int -> UpdateException -> ShowS show :: UpdateException -> String showList :: [UpdateException] -> ShowS |
data PersistException #
Constructors
PersistError Text | |
PersistMarshalError Text | |
PersistInvalidField Text | |
PersistForeignConstraintUnmet Text | |
PersistMongoDBError Text | |
PersistMongoDBUnsupported Text |
Instances
Exception PersistException | |
Defined in Database.Persist.Types.Base Methods toException :: PersistException -> SomeException fromException :: SomeException -> Maybe PersistException displayException :: PersistException -> String | |
Show PersistException | |
Defined in Database.Persist.Types.Base Methods showsPrec :: Int -> PersistException -> ShowS show :: PersistException -> String showList :: [PersistException] -> ShowS |
Constructors
SqlString | |
SqlInt32 | |
SqlInt64 | |
SqlReal | |
SqlNumeric Word32 Word32 | |
SqlBool | |
SqlDay | |
SqlTime | |
SqlDayTime | |
SqlBlob | |
SqlOther Text |
Constructors
UniqueDef | |
Fields
|
Instances
Read UniqueDef | |
Defined in Database.Persist.Types.Base | |
Show UniqueDef | |
Eq UniqueDef | |
Ord UniqueDef | |
Defined in Database.Persist.Types.Base | |
Lift UniqueDef | |
entitiesPrimary :: EntityDef -> NonEmpty FieldDef #
entityPrimary :: EntityDef -> Maybe CompositeDef #
isFieldNotGenerated :: FieldDef -> Bool #
isHaskellField :: FieldDef -> Bool #
keyAndEntityFields :: EntityDef -> NonEmpty FieldDef #
parseFieldAttrs :: [Text] -> [FieldAttr] #
renderCascadeAction :: CascadeAction -> Text #
renderFieldCascade :: FieldCascade -> Text #
(!=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v #
(*=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v #
(+=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v #
(-=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v #
(/<-.) :: forall v typ. PersistField typ => EntityField v typ -> [typ] -> Filter v #
(/=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v #
(<-.) :: forall v typ. PersistField typ => EntityField v typ -> [typ] -> Filter v #
(<.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v #
(<=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v #
(=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v #
(==.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v #
(>.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v #
(>=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v #
toJsonText :: ToJSON j => j -> Text #
limitOffsetOrder :: PersistEntity val => [SelectOpt val] -> (Int, Int, [SelectOpt val]) #
listToJSON :: [PersistValue] -> Text #
mapToJSON :: [(Text, PersistValue)] -> Text #
data ImplicitIdDef #
data MkPersistSettings #
derivePersistField :: String -> Q [Dec] #
derivePersistFieldJSON :: String -> Q [Dec] #
discoverEntities :: Q Exp #
embedEntityDefs :: [EntityDef] -> [UnboundEntityDef] -> [UnboundEntityDef] #
fieldError :: Text -> Text -> Text -> Text #
migrateModels :: [EntityDef] -> Migration #
mkEntityDefList :: String -> [UnboundEntityDef] -> Q [Dec] #
mkPersist :: MkPersistSettings -> [UnboundEntityDef] -> Q [Dec] #
mkPersistSettings :: Type -> MkPersistSettings #
mkPersistWith :: MkPersistSettings -> [EntityDef] -> [UnboundEntityDef] -> Q [Dec] #
parseReferences :: PersistSettings -> Text -> Q Exp #
persistFieldFromEntity :: MkPersistSettings -> UnboundEntityDef -> Q [Dec] #
persistFileWith :: PersistSettings -> FilePath -> Q Exp #
persistLowerCase :: QuasiQuoter #
persistManyFileWith :: PersistSettings -> [FilePath] -> Q Exp #
persistUpperCase :: QuasiQuoter #
persistWith :: PersistSettings -> QuasiQuoter #
pkNewtype :: MkPersistSettings -> UnboundEntityDef -> Bool #
data EntityJSON #
Constructors
EntityJSON | |
Fields
|