Maintainer | Brandon Chinn <brandonchinn178@gmail.com> |
---|---|
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Defines a migration framework for the persistent library.
Synopsis
- hasMigration :: MonadIO m => Migration -> SqlPersistT m Bool
- checkMigration :: MonadIO m => Migration -> SqlPersistT m ()
- module Database.Persist.Migration.Backend
- newtype MigrateSettings = MigrateSettings {
- versionToLabel :: Version -> Maybe String
- data MigrationPath = OperationPath := [Operation]
- type Migration = [MigrationPath]
- type OperationPath = (Version, Version)
- type Version = Int
- (~>) :: Version -> Version -> OperationPath
- opPath :: MigrationPath -> OperationPath
- defaultSettings :: MigrateSettings
- validateMigration :: Migration -> Either String ()
- module Database.Persist.Migration.Operation
- module Database.Persist.Migration.Operation.Types
- module Database.Persist.Migration.Utils.Sql
- data PersistValue where
- 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
- pattern PersistLiteral :: ByteString -> PersistValue
- pattern PersistLiteralEscaped :: ByteString -> PersistValue
- pattern PersistDbSpecific :: ByteString -> PersistValue
- data SqlType
- rawSql :: forall a (m :: Type -> Type) backend. (RawSql a, MonadIO m, BackendCompatible SqlBackend backend) => Text -> [PersistValue] -> ReaderT backend m [a]
Documentation
hasMigration :: MonadIO m => Migration -> SqlPersistT m Bool Source #
True if the persistent library detects more migrations unaccounted for.
checkMigration :: MonadIO m => Migration -> SqlPersistT m () Source #
Fails if the persistent library detects more migrations unaccounted for.
Re-exports
newtype MigrateSettings Source #
Settings to customize migration steps.
MigrateSettings | |
|
data MigrationPath Source #
A path representing the operations needed to run to get from one version of the database schema to the next.
Instances
Show MigrationPath Source # | |
Defined in Database.Persist.Migration.Core showsPrec :: Int -> MigrationPath -> ShowS # show :: MigrationPath -> String # showList :: [MigrationPath] -> ShowS # |
type Migration = [MigrationPath] Source #
A migration list that defines operations to manually migrate a database schema.
type OperationPath = (Version, Version) Source #
The path that an operation takes.
The version of a database. An operation migrates from the given version to another version.
The version must be increasing, such that the lowest version is the first version and the highest version is the most up-to-date version.
A version represents a version of the database schema. In other words, any set of operations taken to get to version X *MUST* all result in the same database schema.
(~>) :: Version -> Version -> OperationPath Source #
An infix constructor for OperationPath
.
opPath :: MigrationPath -> OperationPath Source #
Get the OperationPath in the MigrationPath.
defaultSettings :: MigrateSettings Source #
Default migration settings.
data PersistValue #
A raw value which can be stored in any backend and can be marshalled to
and from a PersistField
.
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 | Intended especially for MongoDB backend |
PersistArray [PersistValue] | Intended especially for PostgreSQL backend for text arrays |
PersistLiteral_ LiteralType ByteString | This constructor is used to specify some raw literal value for the
backend. The Since: persistent-2.12.0.0 |
pattern PersistLiteral :: ByteString -> PersistValue | This pattern synonym used to be a data constructor on Since: persistent-2.12.0.0 |
pattern PersistLiteralEscaped :: ByteString -> PersistValue | This pattern synonym used to be a data constructor on Since: persistent-2.12.0.0 |
pattern PersistDbSpecific :: ByteString -> PersistValue | This pattern synonym used to be a data constructor for the
If you use this, it will overlap a patern match on the 'PersistLiteral_,
Since: persistent-2.12.0.0 |
Instances
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.
SqlString | |
SqlInt32 | |
SqlInt64 | |
SqlReal | |
SqlNumeric Word32 Word32 | |
SqlBool | |
SqlDay | |
SqlTime | |
SqlDayTime | Always uses UTC timezone |
SqlBlob | |
SqlOther Text | a backend-specific name |
:: forall a (m :: Type -> Type) backend. (RawSql a, MonadIO m, BackendCompatible SqlBackend backend) | |
=> Text | SQL statement, possibly with placeholders. |
-> [PersistValue] | Values to fill the placeholders. |
-> ReaderT backend m [a] |
Execute a raw SQL statement and return its results as a
list. If you do not expect a return value, use of
rawExecute
is recommended.
If you're using Entity
s
(which is quite likely), then you
must use entity selection placeholders (double question
mark, ??
). These ??
placeholders are then replaced for
the names of the columns that we need for your entities.
You'll receive an error if you don't use the placeholders.
Please see the Entity
s
documentation for more details.
You may put value placeholders (question marks, ?
) in your
SQL query. These placeholders are then replaced by the values
you pass on the second parameter, already correctly escaped.
You may want to use toPersistValue
to help you constructing
the placeholder values.
Since you're giving a raw SQL statement, you don't get any
guarantees regarding safety. If rawSql
is not able to parse
the results of your query back, then an exception is raised.
However, most common problems are mitigated by using the
entity selection placeholder ??
, and you shouldn't see any
error at all if you're not using Single
.
Some example of rawSql
based on this schema:
share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase| Person name String age Int Maybe deriving Show BlogPost title String authorId PersonId deriving Show |]
Examples based on the above schema:
getPerson :: MonadIO m => ReaderT SqlBackend m [Entity Person] getPerson = rawSql "select ?? from person where name=?" [PersistText "john"] getAge :: MonadIO m => ReaderT SqlBackend m [Single Int] getAge = rawSql "select person.age from person where name=?" [PersistText "john"] getAgeName :: MonadIO m => ReaderT SqlBackend m [(Single Int, Single Text)] getAgeName = rawSql "select person.age, person.name from person where name=?" [PersistText "john"] getPersonBlog :: MonadIO m => ReaderT SqlBackend m [(Entity Person, Entity BlogPost)] getPersonBlog = rawSql "select ??,?? from person,blog_post where person.id = blog_post.author_id" []
Minimal working program for PostgreSQL backend based on the above concepts:
{-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} import Control.Monad.IO.Class (liftIO) import Control.Monad.Logger (runStderrLoggingT) import Database.Persist import Control.Monad.Reader import Data.Text import Database.Persist.Sql import Database.Persist.Postgresql import Database.Persist.TH share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase| Person name String age Int Maybe deriving Show |] conn = "host=localhost dbname=new_db user=postgres password=postgres port=5432" getPerson :: MonadIO m => ReaderT SqlBackend m [Entity Person] getPerson = rawSql "select ?? from person where name=?" [PersistText "sibi"] liftSqlPersistMPool y x = liftIO (runSqlPersistMPool y x) main :: IO () main = runStderrLoggingT $ withPostgresqlPool conn 10 $ liftSqlPersistMPool $ do runMigration migrateAll xs <- getPerson liftIO (print xs)