-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Type-safe, multi-backend data serialization. -- -- Hackage documentation generation is not reliable. For up to date -- documentation, please see: -- http://www.stackage.org/package/persistent. @package persistent @version 2.6 module Database.Persist.Types -- | A Checkmark should be used as a field type whenever a -- uniqueness constraint should guarantee that a certain kind of record -- may appear at most once, but other kinds of records may appear any -- number of times. -- -- NOTE: You need to mark any Checkmark fields as -- nullable (see the following example). -- -- For example, suppose there's a Location entity that -- represents where a user has lived: -- --
--   Location
--       user    UserId
--       name    Text
--       current Checkmark nullable
--   
--       UniqueLocation user current
--   
-- -- The UniqueLocation constraint allows any number of -- Inactive Locations to be current. However, -- there may be at most one current Location per user -- (i.e., either zero or one per user). -- -- This data type works because of the way that SQL treats -- NULLable fields within uniqueness constraints. The SQL -- standard says that NULL values should be considered -- different, so we represent Inactive as SQL NULL, thus -- allowing any number of Inactive records. On the other hand, we -- represent Active as TRUE, so the uniqueness constraint -- will disallow more than one Active record. -- -- Note: There may be DBMSs that do not respect the SQL standard's -- treatment of NULL values on uniqueness constraints, please -- check if this data type works before relying on it. -- -- The SQL BOOLEAN type is used because it's the smallest data -- type available. Note that we never use FALSE, just -- TRUE and NULL. Provides the same behavior Maybe -- () would if () was a valid PersistField. data Checkmark -- | When used on a uniqueness constraint, there may be at most one -- Active record. Active :: Checkmark -- | When used on a uniqueness constraint, there may be any number of -- Inactive records. Inactive :: Checkmark data IsNullable Nullable :: !WhyNullable -> IsNullable NotNullable :: IsNullable -- | The reason why a field is nullable is very important. A field -- that is nullable because of a Maybe tag will have its type -- changed from A to Maybe A. OTOH, a field that is -- nullable because of a nullable tag will remain with the same -- type. data WhyNullable ByMaybeAttr :: WhyNullable ByNullableAttr :: WhyNullable data EntityDef EntityDef :: !HaskellName -> !DBName -> !FieldDef -> ![Attr] -> ![FieldDef] -> ![UniqueDef] -> ![ForeignDef] -> ![Text] -> !(Map Text [ExtraLine]) -> !Bool -> EntityDef [entityHaskell] :: EntityDef -> !HaskellName [entityDB] :: EntityDef -> !DBName [entityId] :: EntityDef -> !FieldDef [entityAttrs] :: EntityDef -> ![Attr] [entityFields] :: EntityDef -> ![FieldDef] [entityUniques] :: EntityDef -> ![UniqueDef] [entityForeigns] :: EntityDef -> ![ForeignDef] [entityDerives] :: EntityDef -> ![Text] [entityExtra] :: EntityDef -> !(Map Text [ExtraLine]) [entitySum] :: EntityDef -> !Bool entityPrimary :: EntityDef -> Maybe CompositeDef entityKeyFields :: EntityDef -> [FieldDef] keyAndEntityFields :: EntityDef -> [FieldDef] type ExtraLine = [Text] newtype HaskellName HaskellName :: Text -> HaskellName [unHaskellName] :: HaskellName -> Text newtype DBName DBName :: Text -> DBName [unDBName] :: DBName -> Text type Attr = Text data FieldType -- | Optional module and name. FTTypeCon :: (Maybe Text) -> Text -> FieldType FTApp :: FieldType -> FieldType -> FieldType FTList :: FieldType -> FieldType data FieldDef FieldDef :: !HaskellName -> !DBName -> !FieldType -> !SqlType -> ![Attr] -> !Bool -> !ReferenceDef -> FieldDef -- | name of the field [fieldHaskell] :: FieldDef -> !HaskellName [fieldDB] :: FieldDef -> !DBName [fieldType] :: FieldDef -> !FieldType [fieldSqlType] :: FieldDef -> !SqlType -- | user annotations for a field [fieldAttrs] :: FieldDef -> ![Attr] -- | a strict field in the data type. Default: true [fieldStrict] :: FieldDef -> !Bool [fieldReference] :: FieldDef -> !ReferenceDef -- | There are 3 kinds of references 1) composite (to fields that exist in -- the record) 2) single field 3) embedded data ReferenceDef NoReference :: ReferenceDef -- | A ForeignRef has a late binding to the EntityDef it references via -- HaskellName and has the Haskell type of the foreign key in the form of -- FieldType ForeignRef :: !HaskellName -> !FieldType -> ReferenceDef EmbedRef :: EmbedEntityDef -> ReferenceDef CompositeRef :: CompositeDef -> ReferenceDef -- | A SelfReference stops an immediate cycle which causes non-termination -- at compile-time (issue #311). SelfReference :: ReferenceDef -- | An EmbedEntityDef is the same as an EntityDef But it is only used for -- fieldReference so it only has data needed for embedding data EmbedEntityDef EmbedEntityDef :: !HaskellName -> ![EmbedFieldDef] -> EmbedEntityDef [embeddedHaskell] :: EmbedEntityDef -> !HaskellName [embeddedFields] :: EmbedEntityDef -> ![EmbedFieldDef] -- | An EmbedFieldDef is the same as a FieldDef But it is only used for -- embeddedFields so it only has data needed for embedding data EmbedFieldDef EmbedFieldDef :: !DBName -> Maybe EmbedEntityDef -> Maybe HaskellName -> EmbedFieldDef [emFieldDB] :: EmbedFieldDef -> !DBName [emFieldEmbed] :: EmbedFieldDef -> Maybe EmbedEntityDef -- | emFieldEmbed can create a cycle (issue #311) when a cycle is -- detected, emFieldEmbed will be Nothing and emFieldCycle -- will be Just [emFieldCycle] :: EmbedFieldDef -> Maybe HaskellName toEmbedEntityDef :: EntityDef -> EmbedEntityDef data UniqueDef UniqueDef :: !HaskellName -> !DBName -> ![(HaskellName, DBName)] -> ![Attr] -> UniqueDef [uniqueHaskell] :: UniqueDef -> !HaskellName [uniqueDBName] :: UniqueDef -> !DBName [uniqueFields] :: UniqueDef -> ![(HaskellName, DBName)] [uniqueAttrs] :: UniqueDef -> ![Attr] data CompositeDef CompositeDef :: ![FieldDef] -> ![Attr] -> CompositeDef [compositeFields] :: CompositeDef -> ![FieldDef] [compositeAttrs] :: CompositeDef -> ![Attr] -- | Used instead of FieldDef to generate a smaller amount of code type ForeignFieldDef = (HaskellName, DBName) data ForeignDef ForeignDef :: !HaskellName -> !DBName -> !HaskellName -> !DBName -> ![(ForeignFieldDef, ForeignFieldDef)] -> ![Attr] -> Bool -> ForeignDef [foreignRefTableHaskell] :: ForeignDef -> !HaskellName [foreignRefTableDBName] :: ForeignDef -> !DBName [foreignConstraintNameHaskell] :: ForeignDef -> !HaskellName [foreignConstraintNameDBName] :: ForeignDef -> !DBName [foreignFields] :: ForeignDef -> ![(ForeignFieldDef, ForeignFieldDef)] [foreignAttrs] :: ForeignDef -> ![Attr] [foreignNullable] :: ForeignDef -> Bool data PersistException -- | Generic Exception PersistError :: Text -> PersistException PersistMarshalError :: Text -> PersistException PersistInvalidField :: Text -> PersistException PersistForeignConstraintUnmet :: Text -> PersistException PersistMongoDBError :: Text -> PersistException PersistMongoDBUnsupported :: Text -> PersistException -- | A raw value which can be stored in any backend and can be marshalled -- to and from a PersistField. data PersistValue PersistText :: Text -> PersistValue PersistByteString :: ByteString -> PersistValue PersistInt64 :: Int64 -> PersistValue PersistDouble :: Double -> PersistValue PersistRational :: Rational -> PersistValue PersistBool :: Bool -> PersistValue PersistDay :: Day -> PersistValue PersistTimeOfDay :: TimeOfDay -> PersistValue PersistUTCTime :: UTCTime -> PersistValue PersistNull :: PersistValue PersistList :: [PersistValue] -> PersistValue PersistMap :: [(Text, PersistValue)] -> PersistValue -- | Intended especially for MongoDB backend PersistObjectId :: ByteString -> PersistValue -- | Using PersistDbSpecific allows you to use types specific to a -- particular backend For example, below is a simple example of the -- PostGIS geography type: -- --
--   data Geo = Geo ByteString
--   
--   instance PersistField Geo where
--     toPersistValue (Geo t) = PersistDbSpecific t
--   
--     fromPersistValue (PersistDbSpecific t) = Right $ Geo $ Data.ByteString.concat ["'", t, "'"]
--     fromPersistValue _ = Left "Geo values must be converted from PersistDbSpecific"
--   
--   instance PersistFieldSql Geo where
--     sqlType _ = SqlOther "GEOGRAPHY(POINT,4326)"
--   
--   toPoint :: Double -> Double -> Geo
--   toPoint lat lon = Geo $ Data.ByteString.concat ["'POINT(", ps $ lon, " ", ps $ lat, ")'"]
--     where ps = Data.Text.pack . show
--   
-- -- If Foo has a geography field, we can then perform insertions like the -- following: -- --
--   insert $ Foo (toPoint 44 44)
--   
PersistDbSpecific :: ByteString -> PersistValue fromPersistValueText :: PersistValue -> Either Text Text -- | A SQL data type. Naming attempts to reflect the underlying Haskell -- datatypes, eg SqlString instead of SqlVarchar. Different SQL databases -- may have different translations for these types. data SqlType SqlString :: SqlType SqlInt32 :: SqlType SqlInt64 :: SqlType SqlReal :: SqlType SqlNumeric :: Word32 -> Word32 -> SqlType SqlBool :: SqlType SqlDay :: SqlType SqlTime :: SqlType -- | Always uses UTC timezone SqlDayTime :: SqlType SqlBlob :: SqlType -- | a backend-specific name SqlOther :: Text -> SqlType data PersistFilter Eq :: PersistFilter Ne :: PersistFilter Gt :: PersistFilter Lt :: PersistFilter Ge :: PersistFilter Le :: PersistFilter In :: PersistFilter NotIn :: PersistFilter BackendSpecificFilter :: Text -> PersistFilter data UpdateException KeyNotFound :: String -> UpdateException UpsertError :: String -> UpdateException data OnlyUniqueException OnlyUniqueException :: String -> OnlyUniqueException data PersistUpdate Assign :: PersistUpdate Add :: PersistUpdate Subtract :: PersistUpdate Multiply :: PersistUpdate Divide :: PersistUpdate BackendSpecificUpdate :: Text -> PersistUpdate data SomePersistField SomePersistField :: a -> SomePersistField -- | Updating a database entity. -- -- Persistent users use combinators to create these. data Update record Update :: EntityField record typ -> typ -> PersistUpdate -> Update record [updateField] :: Update record -> EntityField record typ [updateValue] :: Update record -> typ [updateUpdate] :: Update record -> PersistUpdate BackendUpdate :: (BackendSpecificUpdate (PersistEntityBackend record) record) -> Update record -- | Query options. -- -- Persistent users use these directly. data SelectOpt record Asc :: (EntityField record typ) -> SelectOpt record Desc :: (EntityField record typ) -> SelectOpt record OffsetBy :: Int -> SelectOpt record LimitTo :: Int -> SelectOpt record -- | Filters which are available for select, updateWhere -- and deleteWhere. Each filter constructor specifies the field -- being filtered on, the type of comparison applied (equals, not equals, -- etc) and the argument for the comparison. -- -- Persistent users use combinators to create these. data Filter record Filter :: EntityField record typ -> Either typ [typ] -> PersistFilter -> Filter record [filterField] :: Filter record -> EntityField record typ [filterValue] :: Filter record -> Either typ [typ] [filterFilter] :: Filter record -> PersistFilter -- | convenient for internal use, not needed for the API FilterAnd :: [Filter record] -> Filter record FilterOr :: [Filter record] -> Filter record BackendFilter :: (BackendSpecificFilter (PersistEntityBackend record) record) -> Filter record -- | Datatype that represents an entity, with both its Key and its -- Haskell record representation. -- -- When using a SQL-based backend (such as SQLite or PostgreSQL), an -- Entity may take any number of columns depending on how many -- fields it has. In order to reconstruct your entity on the Haskell -- side, persistent needs all of your entity columns and in the -- right order. Note that you don't need to worry about this when using -- persistent's API since everything is handled correctly behind -- the scenes. -- -- However, if you want to issue a raw SQL command that returns an -- Entity, then you have to be careful with the column order. -- While you could use SELECT Entity.* WHERE ... and that would -- work most of the time, there are times when the order of the columns -- on your database is different from the order that persistent -- expects (for example, if you add a new field in the middle of you -- entity definition and then use the migration code -- -- persistent will expect the column to be in the middle, but -- your DBMS will put it as the last column). So, instead of using a -- query like the one above, you may use rawSql (from the -- Database.Persist.GenericSql module) with its /entity selection -- placeholder/ (a double question mark ??). Using -- rawSql the query above must be written as SELECT ?? WHERE -- ... Then rawSql will replace ?? with the list -- of all columns that we need from your entity in the right order. If -- your query returns two entities (i.e. (Entity backend a, Entity -- backend b)), then you must you use SELECT ??, ?? WHERE -- ..., and so on. data Entity record Entity :: Key record -> record -> Entity record [entityKey] :: Entity record -> Key record [entityVal] :: Entity record -> record module Database.Persist.Quasi -- | Parses a quasi-quoted syntax into a list of entity definitions. parse :: PersistSettings -> Text -> [EntityDef] data PersistSettings PersistSettings :: !(Text -> Text) -> !Bool -> !Text -> PersistSettings [psToDBName] :: PersistSettings -> !(Text -> Text) -- | Whether fields are by default strict. Default value: True. -- -- Since 1.2 [psStrictFields] :: PersistSettings -> !Bool -- | The name of the id column. Default value: id The name of the -- id column can also be changed on a per-model basis -- https://github.com/yesodweb/persistent/wiki/Persistent-entity-syntax -- -- Since 2.0 [psIdName] :: PersistSettings -> !Text upperCaseSettings :: PersistSettings lowerCaseSettings :: PersistSettings nullable :: [Text] -> IsNullable instance GHC.Classes.Eq Database.Persist.Quasi.Token instance GHC.Show.Show Database.Persist.Quasi.Token instance GHC.Show.Show a => GHC.Show.Show (Database.Persist.Quasi.ParseState a) module Database.Persist.Class -- | ToBackendKey converts a PersistEntity Key into a -- BackendKey This can be used by each backend to convert between -- a Key and a plain Haskell type. For Sql, that is done with -- toSqlKey and fromSqlKey. -- -- By default, a PersistEntity uses the default BackendKey -- for its Key and is an instance of ToBackendKey -- -- A Key that instead uses a custom type will not be an instance -- of ToBackendKey. class (PersistEntity record, PersistEntityBackend record ~ backend, PersistCore backend) => ToBackendKey backend record toBackendKey :: ToBackendKey backend record => Key record -> BackendKey backend fromBackendKey :: ToBackendKey backend record => BackendKey backend -> Key record class PersistCore backend where data BackendKey backend where { data family BackendKey backend; } -- | A backwards-compatible alias for those that don't care about -- distinguishing between read and write queries. It signifies the -- assumption that, by default, a backend can write as well as read. type PersistStore a = PersistStoreWrite a 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 -- | Get a record by identifier, if available. get :: (PersistStoreRead backend, MonadIO m, PersistRecordBackend record backend) => Key record -> ReaderT backend m (Maybe record) 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 insert_ record = insert record >> return () insertMany = mapM insert insertMany_ x = insertMany x >> return () insertEntityMany = mapM_ (\ (Entity k record) -> insertKey k record) updateGet key ups = do { update key ups; get key >>= maybe (liftIO $ throwIO $ KeyNotFound $ show key) return } -- | Create a new record in the database, returning an automatically -- created key (in SQL an auto-increment id). insert :: (PersistStoreWrite backend, MonadIO m, PersistRecordBackend record backend) => record -> ReaderT backend m (Key record) -- | Same as insert, but doesn't return a Key. insert_ :: (PersistStoreWrite backend, MonadIO m, PersistRecordBackend record backend) => record -> ReaderT backend m () -- | Create multiple records in the database and return their Keys. -- -- If you don't need the inserted Keys, use insertMany_. -- -- The MongoDB and PostgreSQL backends insert all records and retrieve -- their keys in one database query. -- -- The SQLite and MySQL backends use the slow, default implementation of -- mapM insert. insertMany :: (PersistStoreWrite backend, MonadIO m, PersistRecordBackend record backend) => [record] -> ReaderT backend m [Key record] -- | Same as insertMany, but doesn't return any Keys. -- -- The MongoDB, PostgreSQL, SQLite and MySQL backends insert all records -- in one database query. insertMany_ :: (PersistStoreWrite backend, MonadIO m, PersistRecordBackend record backend) => [record] -> ReaderT backend m () -- | Same as insertMany_, but takes an Entity instead of just -- a record. -- -- Useful when migrating data from one entity to another and want to -- preserve ids. -- -- The MongoDB backend inserts all the entities in one database query. -- -- The SQL backends use the slow, default implementation of mapM_ -- insertKey. insertEntityMany :: (PersistStoreWrite backend, MonadIO m, PersistRecordBackend record backend) => [Entity record] -> ReaderT backend m () -- | Create a new record in the database using the given key. insertKey :: (PersistStoreWrite backend, MonadIO m, PersistRecordBackend record backend) => Key record -> record -> ReaderT backend m () -- | Put the record in the database with the given key. Unlike -- replace, if a record with the given key does not exist then a -- new record will be inserted. repsert :: (PersistStoreWrite backend, MonadIO m, PersistRecordBackend record backend) => Key record -> record -> ReaderT backend m () -- | Replace the record in the database with the given key. Note that the -- result is undefined if such record does not exist, so you must use -- 'insertKey or repsert in these cases. replace :: (PersistStoreWrite backend, MonadIO m, PersistRecordBackend record backend) => Key record -> record -> ReaderT backend m () -- | Delete a specific record by identifier. Does nothing if record does -- not exist. delete :: (PersistStoreWrite backend, MonadIO m, PersistRecordBackend record backend) => Key record -> ReaderT backend m () -- | Update individual fields on a specific record. update :: (PersistStoreWrite backend, MonadIO m, PersistRecordBackend record backend) => Key record -> [Update record] -> ReaderT backend m () -- | Update individual fields on a specific record, and retrieve the -- updated value from the database. -- -- Note that this function will throw an exception if the given key is -- not found in the database. updateGet :: (PersistStoreWrite backend, MonadIO m, PersistRecordBackend record backend) => Key record -> [Update record] -> ReaderT backend m record -- | A convenient alias for common type signatures type PersistRecordBackend record backend = (PersistEntity record, PersistEntityBackend record ~ BaseBackend backend) -- | Same as get, but for a non-null (not Maybe) foreign key Unsafe unless -- your database is enforcing that the foreign key is valid. getJust :: (PersistStoreRead backend, Show (Key record), PersistRecordBackend record backend, MonadIO m) => Key record -> ReaderT backend m record -- | Curry this to make a convenience function that loads an associated -- model. -- --
--   foreign = belongsTo foreignId
--   
belongsTo :: (PersistStoreRead backend, PersistEntity ent1, PersistRecordBackend ent2 backend, MonadIO m) => (ent1 -> Maybe (Key ent2)) -> ent1 -> ReaderT backend m (Maybe ent2) -- | Same as belongsTo, but uses getJust and therefore is -- similarly unsafe. belongsToJust :: (PersistStoreRead backend, PersistEntity ent1, PersistRecordBackend ent2 backend, MonadIO m) => (ent1 -> Key ent2) -> ent1 -> ReaderT backend m ent2 -- | Like insert, but returns the complete Entity. insertEntity :: (PersistStoreWrite backend, PersistRecordBackend e backend, MonadIO m) => e -> ReaderT backend m (Entity e) -- | A backwards-compatible alias for those that don't care about -- distinguishing between read and write queries. It signifies the -- assumption that, by default, a backend can write as well as read. type PersistUnique a = PersistUniqueWrite a -- | Queries against Unique keys (other than the id Key). -- -- Please read the general Persistent documentation to learn how to -- create Unique keys. -- -- Using this with an Entity without a Unique key leads to undefined -- behavior. A few of these functions require a single -- Unique, so using an Entity with multiple Uniques is also -- undefined. In these cases persistent's goal is to throw an exception -- as soon as possible, but persistent is still transitioning to that. -- -- SQL backends automatically create uniqueness constraints, but for -- MongoDB you must manually place a unique index on a field to have a -- uniqueness constraint. class (PersistCore backend, PersistStoreRead backend) => PersistUniqueRead backend -- | Get a record by unique key, if available. Returns also the identifier. getBy :: (PersistUniqueRead backend, MonadIO m, PersistRecordBackend record backend) => Unique record -> ReaderT backend m (Maybe (Entity record)) -- | Some functions in this module (insertUnique, insertBy, -- and replaceUnique) first query the unique indexes to check for -- conflicts. You could instead optimistically attempt to perform the -- operation (e.g. replace instead of replaceUnique). -- However, -- -- class (PersistUniqueRead backend, PersistStoreWrite backend) => PersistUniqueWrite backend where insertUnique datum = do { conflict <- checkUnique datum; case conflict of { Nothing -> Just `liftM` insert datum Just _ -> return Nothing } } upsert record updates = do { uniqueKey <- onlyUnique record; upsertBy uniqueKey record updates } upsertBy uniqueKey record updates = do { mExists <- getBy uniqueKey; k <- case mExists of { Just (Entity k _) -> do { when (null updates) (replace k record); return k } Nothing -> insert record }; Entity k `liftM` updateGet k updates } -- | Delete a specific record by unique key. Does nothing if no record -- matches. deleteBy :: (PersistUniqueWrite backend, MonadIO m, PersistRecordBackend record backend) => Unique record -> ReaderT backend m () -- | Like insert, but returns Nothing when the record -- couldn't be inserted because of a uniqueness constraint. insertUnique :: (PersistUniqueWrite backend, MonadIO m, PersistRecordBackend record backend) => record -> ReaderT backend m (Maybe (Key record)) -- | Update based on a uniqueness constraint or insert: -- -- -- -- Throws an exception if there is more than 1 uniqueness contraint. upsert :: (PersistUniqueWrite backend, MonadIO m, PersistRecordBackend record backend) => record -> [Update record] -> ReaderT backend m (Entity record) -- | Update based on a given uniqueness constraint or insert: -- -- upsertBy :: (PersistUniqueWrite backend, MonadIO m, PersistRecordBackend record backend) => Unique record -> record -> [Update record] -> ReaderT backend m (Entity record) -- | A modification of getBy, which takes the PersistEntity -- itself instead of a Unique record. Returns a record matching -- one of the unique keys. This function makes the most sense on -- entities with a single Unique constructor. getByValue :: (MonadIO m, PersistUniqueRead backend, PersistRecordBackend record backend) => record -> ReaderT backend m (Maybe (Entity record)) -- | Insert a value, checking for conflicts with any unique constraints. If -- a duplicate exists in the database, it is returned as Left. -- Otherwise, the new 'Key is returned as Right. insertBy :: (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend record backend) => record -> ReaderT backend m (Either (Entity record) (Key record)) -- | Attempt to replace the record of the given key with the given new -- record. First query the unique fields to make sure the replacement -- maintains uniqueness constraints. -- -- Return Nothing if the replacement was made. If uniqueness is -- violated, return a Just with the Unique violation -- -- Since 1.2.2.0 replaceUnique :: (MonadIO m, Eq record, Eq (Unique record), PersistRecordBackend record backend, PersistUniqueWrite backend) => Key record -> record -> ReaderT backend m (Maybe (Unique record)) -- | Check whether there are any conflicts for unique keys with this entity -- and existing entities in the database. -- -- Returns Nothing if the entity would be unique, and could thus -- safely be inserted. on a conflict returns the conflicting key checkUnique :: (MonadIO m, PersistRecordBackend record backend, PersistUniqueRead backend) => record -> ReaderT backend m (Maybe (Unique record)) -- | Return the single unique key for a record. onlyUnique :: (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend record backend) => record -> ReaderT backend m (Unique record) -- | A backwards-compatible alias for those that don't care about -- distinguishing between read and write queries. It signifies the -- assumption that, by default, a backend can write as well as read. type PersistQuery a = PersistQueryWrite a -- | Backends supporting conditional read operations. class (PersistCore backend, PersistStoreRead backend) => PersistQueryRead backend where selectFirst filts opts = do { srcRes <- selectSourceRes filts (LimitTo 1 : opts); liftIO $ with srcRes ($$ head) } -- | Get all records matching the given criterion in the specified order. -- Returns also the identifiers. selectSourceRes :: (PersistQueryRead backend, PersistRecordBackend record backend, MonadIO m1, MonadIO m2) => [Filter record] -> [SelectOpt record] -> ReaderT backend m1 (Acquire (Source m2 (Entity record))) -- | Get just the first record for the criterion. selectFirst :: (PersistQueryRead backend, MonadIO m, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m (Maybe (Entity record)) -- | Get the Keys of all records matching the given criterion. selectKeysRes :: (PersistQueryRead backend, MonadIO m1, MonadIO m2, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m1 (Acquire (Source m2 (Key record))) -- | The total number of records fulfilling the given criterion. count :: (PersistQueryRead backend, MonadIO m, PersistRecordBackend record backend) => [Filter record] -> ReaderT backend m Int -- | Backends supporting conditional write operations class (PersistQueryRead backend, PersistStoreWrite backend) => PersistQueryWrite backend -- | Update individual fields on any record matching the given criterion. updateWhere :: (PersistQueryWrite backend, MonadIO m, PersistRecordBackend record backend) => [Filter record] -> [Update record] -> ReaderT backend m () -- | Delete all records matching the given criterion. deleteWhere :: (PersistQueryWrite backend, MonadIO m, PersistRecordBackend record backend) => [Filter record] -> ReaderT backend m () -- | Get all records matching the given criterion in the specified order. -- Returns also the identifiers. selectSource :: (PersistQueryRead (BaseBackend backend), MonadResource m, PersistEntity record, PersistEntityBackend record ~ BaseBackend (BaseBackend backend), MonadReader backend m, HasPersistBackend backend) => [Filter record] -> [SelectOpt record] -> Source m (Entity record) -- | Get the Keys of all records matching the given criterion. selectKeys :: (PersistQueryRead (BaseBackend backend), MonadResource m, PersistEntity record, BaseBackend (BaseBackend backend) ~ PersistEntityBackend record, MonadReader backend m, HasPersistBackend backend) => [Filter record] -> [SelectOpt record] -> Source m (Key record) -- | Call selectSource but return the result as a list. selectList :: (MonadIO m, PersistQueryRead backend, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m [Entity record] -- | Call selectKeys but return the result as a list. selectKeysList :: (MonadIO m, PersistQueryRead backend, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m [Key record] -- | For combinations of backends and entities that support -- cascade-deletion. “Cascade-deletion” means that entries that depend on -- other entries to be deleted will be deleted as well. class (PersistStoreWrite backend, PersistEntity record, BaseBackend backend ~ PersistEntityBackend record) => DeleteCascade record backend -- | Perform cascade-deletion of single database entry. deleteCascade :: (DeleteCascade record backend, MonadIO m) => Key record -> ReaderT backend m () -- | Cascade-deletion of entries satisfying given filters. deleteCascadeWhere :: (MonadIO m, DeleteCascade record backend, PersistQueryWrite backend) => [Filter record] -> ReaderT backend m () -- | Persistent serialized Haskell records to the database. A Database -- Entity (A row in SQL, a document in MongoDB, etc) corresponds -- to a Key plus a Haskell record. -- -- For every Haskell record type stored in the database there is a -- corresponding PersistEntity instance. An instance of -- PersistEntity contains meta-data for the record. PersistEntity also -- helps abstract over different record types. That way the same query -- interface can return a PersistEntity, with each query returning -- different types of Haskell records. -- -- Some advanced type system capabilities are used to make this process -- type-safe. Persistent users usually don't need to understand the class -- associated data and functions. 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 type PersistEntityBackend record data Key record data EntityField record :: * -> * data Unique record where { type family PersistEntityBackend record; data family Key record; data family EntityField record :: * -> *; data family Unique record; } -- | A lower-level key operation. keyToValues :: PersistEntity record => Key record -> [PersistValue] -- | A lower-level key operation. keyFromValues :: PersistEntity record => [PersistValue] -> Either Text (Key record) -- | A meta-operation to retrieve the Key EntityField. persistIdField :: PersistEntity record => EntityField record (Key record) -- | Retrieve the EntityDef meta-data for the record. entityDef :: (PersistEntity record, Monad m) => m record -> EntityDef -- | Return meta-data for a given EntityField. persistFieldDef :: PersistEntity record => EntityField record typ -> FieldDef -- | A meta-operation to get the database fields of a record. toPersistFields :: PersistEntity record => record -> [SomePersistField] -- | A lower-level operation to convert from database values to a Haskell -- record. fromPersistValues :: PersistEntity record => [PersistValue] -> Either Text record -- | A meta operation to retrieve all the Unique keys. persistUniqueKeys :: PersistEntity record => record -> [Unique record] -- | A lower level operation. persistUniqueToFieldNames :: PersistEntity record => Unique record -> [(HaskellName, DBName)] -- | A lower level operation. persistUniqueToValues :: PersistEntity record => Unique record -> [PersistValue] -- | Use a PersistField as a lens. fieldLens :: PersistEntity record => EntityField record field -> (forall f. Functor f => (field -> f field) -> Entity record -> f (Entity record)) -- | A value which can be marshalled to and from a PersistValue. class PersistField a toPersistValue :: PersistField a => a -> PersistValue fromPersistValue :: PersistField a => PersistValue -> Either Text a -- | Represents a value containing all the configuration options for a -- specific backend. This abstraction makes it easier to write code that -- can easily swap backends. class PersistConfig c where type PersistConfigBackend c :: (* -> *) -> * -> * type PersistConfigPool c applyEnv = return where { type family PersistConfigBackend c :: (* -> *) -> * -> *; type family PersistConfigPool c; } -- | Load the config settings from a Value, most likely taken from a -- YAML config file. loadConfig :: PersistConfig c => Value -> Parser c -- | Modify the config settings based on environment variables. applyEnv :: PersistConfig c => c -> IO c -- | Create a new connection pool based on the given config settings. createPoolConfig :: PersistConfig c => c -> IO (PersistConfigPool c) -- | Run a database action by taking a connection from the pool. runPool :: (PersistConfig c, MonadBaseControl IO m, MonadIO m) => c -> PersistConfigBackend c m a -> PersistConfigPool c -> m a -- | Get list of values corresponding to given entity. entityValues :: PersistEntity record => Entity record -> [PersistValue] -- | Class which allows the plucking of a BaseBackend backend from -- some larger type. For example, instance HasPersistBackend -- (SqlReadBackend, Int) where type BaseBackend (SqlReadBackend, Int) = -- SqlBackend persistBackend = unSqlReadBackend . fst class HasPersistBackend backend where type BaseBackend backend where { type family BaseBackend backend; } persistBackend :: HasPersistBackend backend => backend -> BaseBackend backend -- | Class which witnesses that backend is essentially the same as -- BaseBackend backend. That is, they're isomorphic and -- backend is just some wrapper over BaseBackend -- backend. class (HasPersistBackend backend) => IsPersistBackend backend liftPersist :: (MonadIO m, MonadReader backend m, HasPersistBackend backend) => ReaderT (BaseBackend backend) IO b -> m b -- | Predefined toJSON. The resulting JSON looks like {"key": -- 1, "value": {"name": ...}}. -- -- The typical usage is: -- --
--   instance ToJSON (Entity User) where
--       toJSON = keyValueEntityToJSON
--   
keyValueEntityToJSON :: (PersistEntity record, ToJSON record, ToJSON (Key record)) => Entity record -> Value -- | Predefined parseJSON. The input JSON looks like {"key": -- 1, "value": {"name": ...}}. -- -- The typical usage is: -- --
--   instance FromJSON (Entity User) where
--       parseJSON = keyValueEntityFromJSON
--   
keyValueEntityFromJSON :: (PersistEntity record, FromJSON record, FromJSON (Key record)) => Value -> Parser (Entity record) -- | Predefined toJSON. The resulting JSON looks like {"id": -- 1, "name": ...}. -- -- The typical usage is: -- --
--   instance ToJSON (Entity User) where
--       toJSON = entityIdToJSON
--   
entityIdToJSON :: (PersistEntity record, ToJSON record, ToJSON (Key record)) => Entity record -> Value -- | Predefined parseJSON. The input JSON looks like {"id": 1, -- "name": ...}. -- -- The typical usage is: -- --
--   instance FromJSON (Entity User) where
--       parseJSON = entityIdFromJSON
--   
entityIdFromJSON :: (PersistEntity record, FromJSON record, FromJSON (Key record)) => Value -> Parser (Entity record) -- | Convenience function for getting a free PersistField instance -- from a type with JSON instances. -- -- Example usage in combination with fromPersistValueJSON: -- --
--   instance PersistField MyData where
--     fromPersistValue = fromPersistValueJSON
--     toPersistValue = toPersistValueJSON
--   
toPersistValueJSON :: ToJSON a => a -> PersistValue -- | Convenience function for getting a free PersistField instance -- from a type with JSON instances. The JSON parser used will accept JSON -- values other that object and arrays. So, if your instance serializes -- the data to a JSON string, this will still work. -- -- Example usage in combination with toPersistValueJSON: -- --
--   instance PersistField MyData where
--     fromPersistValue = fromPersistValueJSON
--     toPersistValue = toPersistValueJSON
--   
fromPersistValueJSON :: FromJSON a => PersistValue -> Either Text a module Database.Persist.Sql.Types.Internal -- | Class which allows the plucking of a BaseBackend backend from -- some larger type. For example, instance HasPersistBackend -- (SqlReadBackend, Int) where type BaseBackend (SqlReadBackend, Int) = -- SqlBackend persistBackend = unSqlReadBackend . fst class HasPersistBackend backend where type BaseBackend backend where { type family BaseBackend backend; } persistBackend :: HasPersistBackend backend => backend -> BaseBackend backend -- | Class which witnesses that backend is essentially the same as -- BaseBackend backend. That is, they're isomorphic and -- backend is just some wrapper over BaseBackend -- backend. class (HasPersistBackend backend) => IsPersistBackend backend -- | This function is how we actually construct and tag a backend as having -- read or write capabilities. It should be used carefully and only when -- actually constructing a backend. Careless use allows us to -- accidentally run a write query against a read-only database. mkPersistBackend :: IsPersistBackend backend => BaseBackend backend -> backend -- | An SQL backend which can only handle read queries data SqlReadBackend -- | An SQL backend which can handle read or write queries data SqlWriteBackend -- | Useful for running a read query against a backend with unknown -- capabilities. readToUnknown :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlBackend m a -- | Useful for running a read query against a backend with read and write -- capabilities. readToWrite :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlWriteBackend m a -- | Useful for running a write query against an untagged backend with -- unknown capabilities. writeToUnknown :: Monad m => ReaderT SqlWriteBackend m a -> ReaderT SqlBackend m a type LogFunc = Loc -> LogSource -> LogLevel -> LogStr -> IO () data InsertSqlResult ISRSingle :: Text -> InsertSqlResult ISRInsertGet :: Text -> Text -> InsertSqlResult ISRManyKeys :: Text -> [PersistValue] -> InsertSqlResult data Statement Statement :: IO () -> IO () -> ([PersistValue] -> IO Int64) -> (forall m. MonadIO m => [PersistValue] -> Acquire (Source m [PersistValue])) -> Statement [stmtFinalize] :: Statement -> IO () [stmtReset] :: Statement -> IO () [stmtExecute] :: Statement -> [PersistValue] -> IO Int64 [stmtQuery] :: Statement -> forall m. MonadIO m => [PersistValue] -> Acquire (Source m [PersistValue]) data SqlBackend SqlBackend :: (Text -> IO Statement) -> (EntityDef -> [PersistValue] -> InsertSqlResult) -> Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult) -> Maybe (EntityDef -> Text -> Text) -> IORef (Map Text Statement) -> IO () -> ([EntityDef] -> (Text -> IO Statement) -> EntityDef -> IO (Either [Text] [(Bool, Text)])) -> ((Text -> IO Statement) -> IO ()) -> ((Text -> IO Statement) -> IO ()) -> ((Text -> IO Statement) -> IO ()) -> (DBName -> Text) -> Text -> Text -> ((Int, Int) -> Bool -> Text -> Text) -> LogFunc -> SqlBackend [connPrepare] :: SqlBackend -> Text -> IO Statement -- | table name, column names, id name, either 1 or 2 statements to run [connInsertSql] :: SqlBackend -> EntityDef -> [PersistValue] -> InsertSqlResult -- | SQL for inserting many rows and returning their primary keys, for -- backends that support this functioanlity. If Nothing, rows will -- be inserted one-at-a-time using connInsertSql. [connInsertManySql] :: SqlBackend -> Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult) [connUpsertSql] :: SqlBackend -> Maybe (EntityDef -> Text -> Text) [connStmtMap] :: SqlBackend -> IORef (Map Text Statement) [connClose] :: SqlBackend -> IO () [connMigrateSql] :: SqlBackend -> [EntityDef] -> (Text -> IO Statement) -> EntityDef -> IO (Either [Text] [(Bool, Text)]) [connBegin] :: SqlBackend -> (Text -> IO Statement) -> IO () [connCommit] :: SqlBackend -> (Text -> IO Statement) -> IO () [connRollback] :: SqlBackend -> (Text -> IO Statement) -> IO () [connEscapeName] :: SqlBackend -> DBName -> Text [connNoLimit] :: SqlBackend -> Text [connRDBMS] :: SqlBackend -> Text [connLimitOffset] :: SqlBackend -> (Int, Int) -> Bool -> Text -> Text [connLogFunc] :: SqlBackend -> LogFunc -- | A constraint synonym which witnesses that a backend is SQL and can run -- read queries. type SqlBackendCanRead backend = (IsSqlBackend backend, PersistQueryRead backend, PersistStoreRead backend, PersistUniqueRead backend) -- | A constraint synonym which witnesses that a backend is SQL and can run -- read and write queries. type SqlBackendCanWrite backend = (SqlBackendCanRead backend, PersistQueryWrite backend, PersistStoreWrite backend, PersistUniqueWrite backend) -- | Like SqlPersistT but compatible with any SQL backend which -- can handle read queries. type SqlReadT m a = forall backend. (SqlBackendCanRead backend) => ReaderT backend m a -- | Like SqlPersistT but compatible with any SQL backend which -- can handle read and write queries. type SqlWriteT m a = forall backend. (SqlBackendCanWrite backend) => ReaderT backend m a -- | A backend which is a wrapper around SqlBackend. type IsSqlBackend backend = (IsPersistBackend backend, BaseBackend backend ~ SqlBackend) instance Database.Persist.Class.PersistStore.HasPersistBackend Database.Persist.Sql.Types.Internal.SqlBackend instance Database.Persist.Class.PersistStore.IsPersistBackend Database.Persist.Sql.Types.Internal.SqlBackend instance Database.Persist.Class.PersistStore.HasPersistBackend Database.Persist.Sql.Types.Internal.SqlReadBackend instance Database.Persist.Class.PersistStore.IsPersistBackend Database.Persist.Sql.Types.Internal.SqlReadBackend instance Database.Persist.Class.PersistStore.HasPersistBackend Database.Persist.Sql.Types.Internal.SqlWriteBackend instance Database.Persist.Class.PersistStore.IsPersistBackend Database.Persist.Sql.Types.Internal.SqlWriteBackend module Database.Persist -- | Assign a field a value. -- --

Example usage

-- --
--   updateAge :: MonadIO m => ReaderT SqlBackend m ()
--   updateAge = updateWhere [UserName ==. "SPJ" ] [UserAge =. 45]
--   
-- -- Similar to updateWhere which is shown in the above example you -- can use other functions present in the module -- Database.Persist.Class. Note that the first parameter of -- updateWhere is [Filter val] and second parameter is -- [Update val]. By comparing this with the type of ==. and -- =., you can see that they match up in the above usage. -- -- The above query when applied on dataset-1, will produce this: -- --
--   +-----+-----+--------+
--   |id   |name |age     |
--   +-----+-----+--------+
--   |1    |SPJ  |40 -> 45|
--   +-----+-----+--------+
--   |2    |Simon|41      |
--   +-----+-----+--------+
--   
(=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v infixr 3 =. -- | Assign a field by addition (+=). -- --

Example usage

-- --
--   addAge :: MonadIO m => ReaderT SqlBackend m ()
--   addAge = updateWhere [UserName ==. "SPJ" ] [UserAge +=. 1]
--   
-- -- The above query when applied on dataset-1, will produce this: -- --
--   +-----+-----+---------+
--   |id   |name |age      |
--   +-----+-----+---------+
--   |1    |SPJ  |40 -> 41 |
--   +-----+-----+---------+
--   |2    |Simon|41       |
--   +-----+-----+---------+
--   
(+=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v infixr 3 +=. -- | Assign a field by subtraction (-=). -- --

Example usage

-- --
--   subtractAge :: MonadIO m => ReaderT SqlBackend m ()
--   subtractAge = updateWhere [UserName ==. "SPJ" ] [UserAge -=. 1]
--   
-- -- The above query when applied on dataset-1, will produce this: -- --
--   +-----+-----+---------+
--   |id   |name |age      |
--   +-----+-----+---------+
--   |1    |SPJ  |40 -> 39 |
--   +-----+-----+---------+
--   |2    |Simon|41       |
--   +-----+-----+---------+
--   
(-=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v infixr 3 -=. -- | Assign a field by multiplication (*=). -- --

Example usage

-- --
--   multiplyAge :: MonadIO m => ReaderT SqlBackend m ()
--   multiplyAge = updateWhere [UserName ==. "SPJ" ] [UserAge *=. 2]
--   
-- -- The above query when applied on dataset-1, will produce this: -- --
--   +-----+-----+--------+
--   |id   |name |age     |
--   +-----+-----+--------+
--   |1    |SPJ  |40 -> 80|
--   +-----+-----+--------+
--   |2    |Simon|41      |
--   +-----+-----+--------+
--   
(*=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v infixr 3 *=. -- | Assign a field by division (/=). -- --

Example usage

-- --
--   divideAge :: MonadIO m => ReaderT SqlBackend m ()
--   divideAge = updateWhere [UserName ==. "SPJ" ] [UserAge /=. 2]
--   
-- -- The above query when applied on dataset-1, will produce this: -- --
--   +-----+-----+---------+
--   |id   |name |age      |
--   +-----+-----+---------+
--   |1    |SPJ  |40 -> 20 |
--   +-----+-----+---------+
--   |2    |Simon|41       |
--   +-----+-----+---------+
--   
(/=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v infixr 3 /=. -- | Check for equality. -- --

Example usage

-- --
--   selectSPJ :: MonadIO m => ReaderT SqlBackend m [Entity User]
--   selectSPJ = selectList [UserName ==. "SPJ" ] []
--   
-- -- The above query when applied on dataset-1, will produce this: -- --
--   +-----+-----+-----+
--   |id   |name |age  |
--   +-----+-----+-----+
--   |1    |SPJ  |40   |
--   +-----+-----+-----+
--   
(==.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v infix 4 ==. -- | Non-equality check. -- --

Example usage

-- --
--   selectSimon :: MonadIO m => ReaderT SqlBackend m [Entity User]
--   selectSimon = selectList [UserName !=. "SPJ" ] []
--   
-- -- The above query when applied on dataset-1, will produce this: -- --
--   +-----+-----+-----+
--   |id   |name |age  |
--   +-----+-----+-----+
--   |2    |Simon|41   |
--   +-----+-----+-----+
--   
(!=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v infix 4 !=. -- | Less-than check. -- --

Example usage

-- --
--   selectLessAge :: MonadIO m => ReaderT SqlBackend m [Entity User]
--   selectLessAge = selectList [UserAge <. 41 ] []
--   
-- -- The above query when applied on dataset-1, will produce this: -- --
--   +-----+-----+-----+
--   |id   |name |age  |
--   +-----+-----+-----+
--   |1    |SPJ  |40   |
--   +-----+-----+-----+
--   
(<.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v infix 4 <. -- | Greater-than check. -- --

Example usage

-- --
--   selectGreaterAge :: MonadIO m => ReaderT SqlBackend m [Entity User]
--   selectGreaterAge = selectList [UserAge >. 40 ] []
--   
-- -- The above query when applied on dataset-1, will produce this: -- --
--   +-----+-----+-----+
--   |id   |name |age  |
--   +-----+-----+-----+
--   |2    |Simon|41   |
--   +-----+-----+-----+
--   
(>.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v infix 4 >. -- | Less-than or equal check. -- --

Example usage

-- --
--   selectLessEqualAge :: MonadIO m => ReaderT SqlBackend m [Entity User]
--   selectLessEqualAge = selectList [UserAge <=. 40 ] []
--   
-- -- The above query when applied on dataset-1, will produce this: -- --
--   +-----+-----+-----+
--   |id   |name |age  |
--   +-----+-----+-----+
--   |1    |SPJ  |40   |
--   +-----+-----+-----+
--   
(<=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v infix 4 <=. -- | Greater-than or equal check. -- --

Example usage

-- --
--   selectGreaterEqualAge :: MonadIO m => ReaderT SqlBackend m [Entity User]
--   selectGreaterEqualAge = selectList [UserAge >=. 41 ] []
--   
-- -- The above query when applied on dataset-1, will produce this: -- --
--   +-----+-----+-----+
--   |id   |name |age  |
--   +-----+-----+-----+
--   |2    |Simon|41   |
--   +-----+-----+-----+
--   
(>=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v infix 4 >=. -- | Check if value is in given list. -- --

Example usage

-- --
--   selectUsers :: MonadIO m => ReaderT SqlBackend m [Entity User]
--   selectUsers = selectList [UserAge <-. [40, 41]] []
--   
-- -- The above query when applied on dataset-1, will produce this: -- --
--   +-----+-----+-----+
--   |id   |name |age  |
--   +-----+-----+-----+
--   |1    |SPJ  |40   |
--   +-----+-----+-----+
--   |2    |Simon|41   |
--   +-----+-----+-----+
--   
-- --
--   selectSPJ :: MonadIO m => ReaderT SqlBackend m [Entity User]
--   selectSPJ = selectList [UserAge <-. [40]] []
--   
-- -- The above query when applied on dataset-1, will produce this: -- --
--   +-----+-----+-----+
--   |id   |name |age  |
--   +-----+-----+-----+
--   |1    |SPJ  |40   |
--   +-----+-----+-----+
--   
(<-.) :: forall v typ. PersistField typ => EntityField v typ -> [typ] -> Filter v infix 4 <-. -- | Check if value is not in given list. -- --

Example usage

-- --
--   selectSimon :: MonadIO m => ReaderT SqlBackend m [Entity User]
--   selectSimon = selectList [UserAge /<-. [40]] []
--   
-- -- The above query when applied on dataset-1, will produce this: -- --
--   +-----+-----+-----+
--   |id   |name |age  |
--   +-----+-----+-----+
--   |2    |Simon|41   |
--   +-----+-----+-----+
--   
(/<-.) :: forall v typ. PersistField typ => EntityField v typ -> [typ] -> Filter v infix 4 /<-. -- | The OR of two lists of filters. For example: -- --
--   selectList
--       ([ PersonAge >. 25
--        , PersonAge <. 30 ] ||.
--        [ PersonIncome >. 15000
--        , PersonIncome <. 25000 ])
--       []
--   
-- -- will filter records where a person's age is between 25 and 30 -- or a person's income is between (15000 and 25000). -- -- If you are looking for an (&&.) operator to do (A -- AND B AND (C OR D)) you can use the (++) operator -- instead as there is no (&&.). For example: -- --
--   selectList
--       ([ PersonAge >. 25
--        , PersonAge <. 30 ] ++
--       ([PersonCategory ==. 1] ||.
--        [PersonCategory ==. 5]))
--       []
--   
-- -- will filter records where a person's age is between 25 and 30 -- and (person's category is either 1 or 5). (||.) :: forall v. [Filter v] -> [Filter v] -> [Filter v] infixl 3 ||. -- | Convert list of PersistValues into textual representation of -- JSON object. This is a type-constrained synonym for toJsonText. listToJSON :: [PersistValue] -> Text -- | Convert map (list of tuples) into textual representation of JSON -- object. This is a type-constrained synonym for toJsonText. mapToJSON :: [(Text, PersistValue)] -> Text -- | A more general way to convert instances of ToJSON type class to -- strict text Text. toJsonText :: ToJSON j => j -> Text -- | FIXME Add documentation to that. getPersistMap :: PersistValue -> Either Text [(Text, PersistValue)] -- | FIXME What's this exactly? limitOffsetOrder :: PersistEntity val => [SelectOpt val] -> (Int, Int, [SelectOpt val]) module Database.Persist.Sql.Util parseEntityValues :: PersistEntity record => EntityDef -> [PersistValue] -> Either Text (Entity record) entityColumnNames :: EntityDef -> SqlBackend -> [Sql] keyAndEntityColumnNames :: EntityDef -> SqlBackend -> [Sql] entityColumnCount :: EntityDef -> Int isIdField :: PersistEntity record => EntityField record typ -> Bool hasCompositeKey :: EntityDef -> Bool dbIdColumns :: SqlBackend -> EntityDef -> [Text] dbIdColumnsEsc :: (DBName -> Text) -> EntityDef -> [Text] dbColumns :: SqlBackend -> EntityDef -> [Text] module Database.Persist.Sql -- | Deprecated synonym for SqlBackend. -- | Deprecated: Please use SqlBackend instead type Connection = SqlBackend data Column Column :: !DBName -> !Bool -> !SqlType -> !(Maybe Text) -> !(Maybe DBName) -> !(Maybe Integer) -> !(Maybe (DBName, DBName)) -> Column [cName] :: Column -> !DBName [cNull] :: Column -> !Bool [cSqlType] :: Column -> !SqlType [cDefault] :: Column -> !(Maybe Text) [cDefaultConstraintName] :: Column -> !(Maybe DBName) [cMaxLen] :: Column -> !(Maybe Integer) [cReference] :: Column -> !(Maybe (DBName, DBName)) data PersistentSqlException StatementAlreadyFinalized :: Text -> PersistentSqlException Couldn'tGetSQLConnection :: PersistentSqlException type SqlPersistT = ReaderT SqlBackend -- | Deprecated: Please use SqlPersistT instead type SqlPersist = SqlPersistT type SqlPersistM = SqlPersistT (NoLoggingT (ResourceT IO)) type Sql = Text type CautiousMigration = [(Bool, Sql)] type Migration = WriterT [Text] (WriterT CautiousMigration (ReaderT SqlBackend IO)) () type ConnectionPool = Pool SqlBackend -- | A single column (see rawSql). Any PersistField may -- be used here, including PersistValue (which does not do any -- processing). newtype Single a Single :: a -> Single a [unSingle] :: Single a -> a data SqlBackend SqlBackend :: (Text -> IO Statement) -> (EntityDef -> [PersistValue] -> InsertSqlResult) -> Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult) -> Maybe (EntityDef -> Text -> Text) -> IORef (Map Text Statement) -> IO () -> ([EntityDef] -> (Text -> IO Statement) -> EntityDef -> IO (Either [Text] [(Bool, Text)])) -> ((Text -> IO Statement) -> IO ()) -> ((Text -> IO Statement) -> IO ()) -> ((Text -> IO Statement) -> IO ()) -> (DBName -> Text) -> Text -> Text -> ((Int, Int) -> Bool -> Text -> Text) -> LogFunc -> SqlBackend [connPrepare] :: SqlBackend -> Text -> IO Statement -- | table name, column names, id name, either 1 or 2 statements to run [connInsertSql] :: SqlBackend -> EntityDef -> [PersistValue] -> InsertSqlResult -- | SQL for inserting many rows and returning their primary keys, for -- backends that support this functioanlity. If Nothing, rows will -- be inserted one-at-a-time using connInsertSql. [connInsertManySql] :: SqlBackend -> Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult) [connUpsertSql] :: SqlBackend -> Maybe (EntityDef -> Text -> Text) [connStmtMap] :: SqlBackend -> IORef (Map Text Statement) [connClose] :: SqlBackend -> IO () [connMigrateSql] :: SqlBackend -> [EntityDef] -> (Text -> IO Statement) -> EntityDef -> IO (Either [Text] [(Bool, Text)]) [connBegin] :: SqlBackend -> (Text -> IO Statement) -> IO () [connCommit] :: SqlBackend -> (Text -> IO Statement) -> IO () [connRollback] :: SqlBackend -> (Text -> IO Statement) -> IO () [connEscapeName] :: SqlBackend -> DBName -> Text [connNoLimit] :: SqlBackend -> Text [connRDBMS] :: SqlBackend -> Text [connLimitOffset] :: SqlBackend -> (Int, Int) -> Bool -> Text -> Text [connLogFunc] :: SqlBackend -> LogFunc -- | An SQL backend which can only handle read queries data SqlReadBackend -- | An SQL backend which can handle read or write queries data SqlWriteBackend data Statement Statement :: IO () -> IO () -> ([PersistValue] -> IO Int64) -> (forall m. MonadIO m => [PersistValue] -> Acquire (Source m [PersistValue])) -> Statement [stmtFinalize] :: Statement -> IO () [stmtReset] :: Statement -> IO () [stmtExecute] :: Statement -> [PersistValue] -> IO Int64 [stmtQuery] :: Statement -> forall m. MonadIO m => [PersistValue] -> Acquire (Source m [PersistValue]) type LogFunc = Loc -> LogSource -> LogLevel -> LogStr -> IO () data InsertSqlResult ISRSingle :: Text -> InsertSqlResult ISRInsertGet :: Text -> Text -> InsertSqlResult ISRManyKeys :: Text -> [PersistValue] -> InsertSqlResult -- | Useful for running a read query against a backend with unknown -- capabilities. readToUnknown :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlBackend m a -- | Useful for running a read query against a backend with read and write -- capabilities. readToWrite :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlWriteBackend m a -- | Useful for running a write query against an untagged backend with -- unknown capabilities. writeToUnknown :: Monad m => ReaderT SqlWriteBackend m a -> ReaderT SqlBackend m a -- | A constraint synonym which witnesses that a backend is SQL and can run -- read queries. type SqlBackendCanRead backend = (IsSqlBackend backend, PersistQueryRead backend, PersistStoreRead backend, PersistUniqueRead backend) -- | A constraint synonym which witnesses that a backend is SQL and can run -- read and write queries. type SqlBackendCanWrite backend = (SqlBackendCanRead backend, PersistQueryWrite backend, PersistStoreWrite backend, PersistUniqueWrite backend) -- | Like SqlPersistT but compatible with any SQL backend which -- can handle read queries. type SqlReadT m a = forall backend. (SqlBackendCanRead backend) => ReaderT backend m a -- | Like SqlPersistT but compatible with any SQL backend which -- can handle read and write queries. type SqlWriteT m a = forall backend. (SqlBackendCanWrite backend) => ReaderT backend m a -- | A backend which is a wrapper around SqlBackend. type IsSqlBackend backend = (IsPersistBackend backend, BaseBackend backend ~ SqlBackend) -- | Class for data types that may be retrived from a rawSql -- query. class RawSql a -- | Number of columns that this data type needs and the list of -- substitutions for SELECT placeholders ??. rawSqlCols :: RawSql a => (DBName -> Text) -> a -> (Int, [Text]) -- | A string telling the user why the column count is what it is. rawSqlColCountReason :: RawSql a => a -> String -- | Transform a row of the result into the data type. rawSqlProcessRow :: RawSql a => [PersistValue] -> Either Text a class PersistField a => PersistFieldSql a sqlType :: PersistFieldSql a => Proxy a -> SqlType -- | 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. runSqlPool :: (MonadBaseControl IO m, IsSqlBackend backend) => ReaderT backend m a -> Pool backend -> m a -- | Like withResource, but times out the operation if resource -- allocation does not complete within the given timeout period. -- -- Since 2.0.0 withResourceTimeout :: forall a m b. (MonadBaseControl IO m) => Int -> Pool a -> (a -> m b) -> m (Maybe b) runSqlConn :: (MonadBaseControl IO m, IsSqlBackend backend) => ReaderT backend m a -> backend -> m a runSqlPersistM :: (IsSqlBackend backend) => ReaderT backend (NoLoggingT (ResourceT IO)) a -> backend -> IO a runSqlPersistMPool :: (IsSqlBackend backend) => ReaderT backend (NoLoggingT (ResourceT IO)) a -> Pool backend -> IO a liftSqlPersistMPool :: (MonadIO m, IsSqlBackend backend) => ReaderT backend (NoLoggingT (ResourceT IO)) a -> Pool backend -> m a withSqlPool :: (MonadIO m, MonadLogger m, MonadBaseControl IO m, IsSqlBackend backend) => (LogFunc -> IO backend) -> Int -> (Pool backend -> m a) -> m a createSqlPool :: (MonadIO m, MonadLogger m, MonadBaseControl IO m, IsSqlBackend backend) => (LogFunc -> IO backend) -> Int -> m (Pool backend) askLogFunc :: forall m. (MonadBaseControl IO m, MonadLogger m) => m LogFunc withSqlConn :: (MonadIO m, MonadBaseControl IO m, MonadLogger m, IsSqlBackend backend) => (LogFunc -> IO backend) -> (backend -> m a) -> m a close' :: (IsSqlBackend backend) => backend -> IO () parseMigration :: MonadIO m => Migration -> ReaderT SqlBackend m (Either [Text] CautiousMigration) parseMigration' :: MonadIO m => Migration -> ReaderT SqlBackend m (CautiousMigration) printMigration :: MonadIO m => Migration -> ReaderT SqlBackend m () showMigration :: MonadIO m => Migration -> ReaderT SqlBackend m [Text] getMigration :: MonadIO m => Migration -> ReaderT SqlBackend m [Sql] runMigration :: MonadIO m => Migration -> ReaderT SqlBackend m () -- | Same as runMigration, but returns a list of the SQL commands -- executed instead of printing them to stderr. runMigrationSilent :: (MonadBaseControl IO m, MonadIO m) => Migration -> ReaderT SqlBackend m [Text] runMigrationUnsafe :: MonadIO m => Migration -> ReaderT SqlBackend m () migrate :: [EntityDef] -> EntityDef -> Migration withRawQuery :: MonadIO m => Text -> [PersistValue] -> Sink [PersistValue] IO a -> ReaderT SqlBackend m a toSqlKey :: ToBackendKey SqlBackend record => Int64 -> Key record fromSqlKey :: ToBackendKey SqlBackend record => Key record -> Int64 -- | 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 getFieldName :: forall record typ m backend. (PersistEntity record, PersistEntityBackend record ~ SqlBackend, IsSqlBackend backend, Monad m) => EntityField record typ -> ReaderT backend m Text -- | 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 getTableName :: forall record m backend. (PersistEntity record, PersistEntityBackend record ~ SqlBackend, IsSqlBackend backend, Monad m) => record -> ReaderT backend m Text -- | useful for a backend to implement tableName by adding escaping tableDBName :: (PersistEntity record) => record -> DBName -- | useful for a backend to implement fieldName by adding escaping fieldDBName :: forall record typ. (PersistEntity record) => EntityField record typ -> DBName rawQuery :: (MonadResource m, MonadReader env m, HasPersistBackend env, BaseBackend env ~ SqlBackend) => Text -> [PersistValue] -> Source m [PersistValue] rawQueryRes :: (MonadIO m1, MonadIO m2, IsSqlBackend env) => Text -> [PersistValue] -> ReaderT env m1 (Acquire (Source m2 [PersistValue])) -- | Execute a raw SQL statement rawExecute :: MonadIO m => Text -> [PersistValue] -> ReaderT SqlBackend m () -- | Execute a raw SQL statement and return the number of rows it has -- modified. rawExecuteCount :: (MonadIO m, IsSqlBackend backend) => Text -> [PersistValue] -> ReaderT backend m Int64 -- | Execute a raw SQL statement and return its results as a list. -- -- If you're using Entitys (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 -- Entitys 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)
--   
rawSql :: (RawSql a, MonadIO m) => Text -> [PersistValue] -> ReaderT SqlBackend m [a] -- | Same as deleteWhere, but returns the number of rows affected. -- -- Since 1.1.5 deleteWhereCount :: (PersistEntity val, MonadIO m, PersistEntityBackend val ~ SqlBackend, IsSqlBackend backend) => [Filter val] -> ReaderT backend m Int64 -- | Same as updateWhere, but returns the number of rows affected. -- -- Since 1.1.5 updateWhereCount :: (PersistEntity val, MonadIO m, SqlBackend ~ PersistEntityBackend val, IsSqlBackend backend) => [Filter val] -> [Update val] -> ReaderT backend m Int64 -- | Commit the current transaction and begin a new one. -- -- Since 1.2.0 transactionSave :: MonadIO m => ReaderT SqlBackend m () -- | Roll back the current transaction and begin a new one. -- -- Since 1.2.0 transactionUndo :: MonadIO m => ReaderT SqlBackend m () getStmtConn :: SqlBackend -> Text -> IO Statement -- | Create the list of columns for the given entity. mkColumns :: [EntityDef] -> EntityDef -> ([Column], [UniqueDef], [ForeignDef]) defaultAttribute :: [Attr] -> Maybe Text -- | Generates sql for limit and offset for postgres, sqlite and mysql. decorateSQLWithLimitOffset :: Text -> (Int, Int) -> Bool -> Text -> Text