Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module provides the tools for defining your database schema and using it to generate Haskell data types and migrations.
For documentation on the domain specific language used for defining database models, see Database.Persist.Quasi.
Synopsis
- persistWith :: PersistSettings -> QuasiQuoter
- persistUpperCase :: QuasiQuoter
- persistLowerCase :: QuasiQuoter
- persistFileWith :: PersistSettings -> FilePath -> Q Exp
- persistManyFileWith :: PersistSettings -> [FilePath] -> Q Exp
- mkPersist :: MkPersistSettings -> [UnboundEntityDef] -> Q [Dec]
- mkPersistWith :: MkPersistSettings -> [EntityDef] -> [UnboundEntityDef] -> Q [Dec]
- data MkPersistSettings
- mkPersistSettings :: Type -> MkPersistSettings
- sqlSettings :: MkPersistSettings
- mpsBackend :: MkPersistSettings -> Type
- mpsGeneric :: MkPersistSettings -> Bool
- mpsPrefixFields :: MkPersistSettings -> Bool
- mpsFieldLabelModifier :: MkPersistSettings -> Text -> Text -> Text
- mpsConstraintLabelModifier :: MkPersistSettings -> Text -> Text -> Text
- mpsEntityJSON :: MkPersistSettings -> Maybe EntityJSON
- mpsGenerateLenses :: MkPersistSettings -> Bool
- mpsDeriveInstances :: MkPersistSettings -> [Name]
- mpsCamelCaseCompositeKeySelector :: MkPersistSettings -> Bool
- data EntityJSON = EntityJSON {}
- data ImplicitIdDef
- setImplicitIdDef :: ImplicitIdDef -> MkPersistSettings -> MkPersistSettings
- mkMigrate :: String -> [UnboundEntityDef] -> Q [Dec]
- migrateModels :: [EntityDef] -> Migration
- discoverEntities :: Q Exp
- mkEntityDefList :: String -> [UnboundEntityDef] -> Q [Dec]
- share :: [[a] -> Q [Dec]] -> [a] -> Q [Dec]
- derivePersistField :: String -> Q [Dec]
- derivePersistFieldJSON :: String -> Q [Dec]
- persistFieldFromEntity :: MkPersistSettings -> UnboundEntityDef -> Q [Dec]
- lensPTH :: (s -> a) -> (s -> b -> t) -> Lens s t a b
- parseReferences :: PersistSettings -> Text -> Q Exp
- embedEntityDefs :: [EntityDef] -> [UnboundEntityDef] -> [UnboundEntityDef]
- fieldError :: Text -> Text -> Text -> Text
- class PersistEntity record => AtLeastOneUniqueKey record where
- requireUniquesP :: record -> NonEmpty (Unique record)
- class PersistEntity record => OnlyOneUniqueKey record where
- onlyUniqueP :: record -> Unique record
- pkNewtype :: MkPersistSettings -> UnboundEntityDef -> Bool
Parse entity defs
persistWith :: PersistSettings -> QuasiQuoter Source #
Converts a quasi-quoted syntax into a list of entity definitions, to be used as input to the template haskell generation code (mkPersist).
persistUpperCase :: QuasiQuoter Source #
Apply persistWith
to upperCaseSettings
.
persistLowerCase :: QuasiQuoter Source #
Apply persistWith
to lowerCaseSettings
.
persistFileWith :: PersistSettings -> FilePath -> Q Exp Source #
Same as persistWith
, but uses an external file instead of a
quasiquotation. The recommended file extension is .persistentmodels
.
persistManyFileWith :: PersistSettings -> [FilePath] -> Q Exp Source #
Same as persistFileWith
, but uses several external files instead of
one. Splitting your Persistent definitions into multiple modules can
potentially dramatically speed up compile times.
The recommended file extension is .persistentmodels
.
Examples
Split your Persistent definitions into multiple files (models1
, models2
),
then create a new module for each new file and run mkPersist
there:
-- Model1.hsshare
[mkPersist
sqlSettings
] $(persistFileWith
lowerCaseSettings
"models1")
-- Model2.hsshare
[mkPersist
sqlSettings
] $(persistFileWith
lowerCaseSettings
"models2")
Use persistManyFileWith
to create your migrations:
-- Migrate.hsmkMigrate
"migrateAll" $(persistManyFileWith
lowerCaseSettings
["models1.persistentmodels","models2.persistentmodels"])
Tip: To get the same import behavior as if you were declaring all your models in
one file, import your new files as Name
into another file, then export module Name
.
This approach may be used in the future to reduce memory usage during compilation, but so far we've only seen mild reductions.
See persistent#778 and persistent#791 for more details.
Since: 2.5.4
Turn EntityDef
s into types
mkPersist :: MkPersistSettings -> [UnboundEntityDef] -> Q [Dec] Source #
Create data types and appropriate PersistEntity
instances for the given
UnboundEntityDef
s.
This function should be used if you are only defining a single block of
Persistent models for the entire application. If you intend on defining
multiple blocks in different fiels, see mkPersistWith
which allows you
to provide existing entity definitions so foreign key references work.
Example:
mkPersistsqlSettings
[persistLowerCase
| User name Text age Int Dog name Text owner UserId |]
Example from a file:
mkPersistsqlSettings
$(persistFileWith
lowerCaseSettings
"models.persistentmodels")
For full information on the QuasiQuoter
syntax, see
Database.Persist.Quasi documentation.
mkPersistWith :: MkPersistSettings -> [EntityDef] -> [UnboundEntityDef] -> Q [Dec] Source #
Like mkPersist
, but allows you to provide a [
representing the predefined entities. This function will include those
EntityDef
]EntityDef
when looking for foreign key references.
You should use this if you intend on defining Persistent models in multiple files.
Suppose we define a table Foo
which has no dependencies.
module DB.Foo wheremkPersistWith
sqlSettings
[] [persistLowerCase
| Foo name Text |]
Then, we define a table Bar
which depends on Foo
:
module DB.Bar where import DB.FoomkPersistWith
sqlSettings
[entityDef (Proxy :: Proxy Foo)] [persistLowerCase
| Bar fooId FooId |]
Writing out the list of EntityDef
can be annoying. The
$(
shortcut will work to reduce this boilerplate.discoverEntities
)
module DB.Quux where import DB.Foo import DB.BarmkPersistWith
sqlSettings
$(discoverEntities
) [persistLowerCase
| Quux name Text fooId FooId barId BarId |]
Since: 2.13.0.0
Configuring Entity Definition
data MkPersistSettings Source #
Settings to be passed to the mkPersist
function.
:: Type | Value for |
-> MkPersistSettings |
Create an MkPersistSettings
with default values.
sqlSettings :: MkPersistSettings Source #
Use the SqlPersist
backend.
Record Fields (for update/viewing settings)
mpsBackend :: MkPersistSettings -> Type Source #
Which database backend we're using. This type is used for the
PersistEntityBackend
associated type in the entities that are
generated.
If the mpsGeneric
value is set to True
, then this type is used for
the non-Generic type alias. The data and type will be named:
data ModelGeneric backend = Model { ... }
And, for convenience's sake, we provide a type alias:
type Model = ModelGeneric $(the type you give here)
mpsGeneric :: MkPersistSettings -> Bool Source #
Deprecated: The mpsGeneric function adds a considerable amount of overhead and complexity to the library without bringing significant benefit. We would like to remove it. If you require this feature, please comment on the linked GitHub issue, and we'll either keep it around, or we can figure out a nicer way to solve your problem. Github: https://github.com/yesodweb/persistent/issues/1204
Create generic types that can be used with multiple backends. Good for reusable code, but makes error messages harder to understand. Default: False.
mpsPrefixFields :: MkPersistSettings -> Bool Source #
Prefix field names with the model name. Default: True.
Note: this field is deprecated. Use the mpsFieldLabelModifier and
mpsConstraintLabelModifier
instead.
mpsFieldLabelModifier :: MkPersistSettings -> Text -> Text -> Text Source #
Customise the field accessors and lens names using the entity and field name. Both arguments are upper cased.
Default: appends entity and field.
Note: this setting is ignored if mpsPrefixFields is set to False.
Since: 2.11.0.0
mpsConstraintLabelModifier :: MkPersistSettings -> Text -> Text -> Text Source #
Customise the Constraint names using the entity and field name. The result should be a valid haskell type (start with an upper cased letter).
Default: appends entity and field
Note: this setting is ignored if mpsPrefixFields is set to False.
Since: 2.11.0.0
mpsEntityJSON :: MkPersistSettings -> Maybe EntityJSON Source #
Generate ToJSON
/FromJSON
instances for each model types. If it's
Nothing
, no instances will be generated. Default:
JustEntityJSON
{entityToJSON
= 'entityIdToJSON ,entityFromJSON
= 'entityIdFromJSON }
mpsGenerateLenses :: MkPersistSettings -> Bool Source #
Instead of generating normal field accessors, generator lens-style accessors.
Default: False
Since: 1.3.1
mpsDeriveInstances :: MkPersistSettings -> [Name] Source #
Automatically derive these typeclass instances for all record and key types.
Default: []
Since: 2.8.1
mpsCamelCaseCompositeKeySelector :: MkPersistSettings -> Bool Source #
Should we generate composite key accessors in the correct CamelCase style.
If the mpsCamelCaseCompositeKeySelector
value is set to False
,
then the field part of the accessor starts with the lowercase.
This is a legacy style.
data Key CompanyUser = CompanyUserKey { companyUserKeycompanyId :: CompanyId , companyUserKeyuserId :: UserId }
If the mpsCamelCaseCompositeKeySelector
value is set to True
,
then field accessors are generated in CamelCase style.
data Key CompanyUser = CompanyUserKey { companyUserKeyCompanyId :: CompanyId , companyUserKeyUserId :: UserId }
data EntityJSON Source #
EntityJSON | |
|
Implicit ID Columns
data ImplicitIdDef Source #
A specification for how the implied ID columns are created.
By default, persistent
will give each table a default column named id
(customizable by PersistSettings
), and the column type will be whatever
you'd expect from
. For The BackendKey
yourBackendTypeSqlBackend
type,
this is an auto incrementing integer primary key.
You might want to give a different example. A common use case in postgresql is to use the UUID type, and automatically generate them using a SQL function.
Previously, you'd need to add a custom Id
annotation for each model.
User Id UUID default="uuid_generate_v1mc()" name Text Dog Id UUID default="uuid_generate_v1mc()" name Text user UserId
Now, you can simply create an ImplicitIdDef
that corresponds to this
declaration.
newtype UUID = UUIDByteString
instancePersistField
UUID wheretoPersistValue
(UUID bs) =PersistLiteral_
Escaped
bsfromPersistValue
pv = case pv of PersistLiteral_ Escaped bs -> Right (UUID bs) _ -> Left "nope" instancePersistFieldSql
UUID wheresqlType
_ =SqlOther
UUID
With this instance at the ready, we can now create our implicit definition:
uuidDef :: ImplicitIdDef uuidDef = mkImplicitIdDef @UUID "uuid_generate_v1mc()"
And we can use setImplicitIdDef
to use this with the MkPersistSettings
for our block.
mkPersist (setImplicitIdDef uuidDef sqlSettings) [persistLowerCase| ... |]
TODO: either explain interaction with mkMigrate or fix it. see issue #1249 for more details.
Since: 2.13.0.0
setImplicitIdDef :: ImplicitIdDef -> MkPersistSettings -> MkPersistSettings Source #
Set the ImplicitIdDef
in the given MkPersistSettings
. The default
value is autoIncrementingInteger
.
Since: 2.13.0.0
Various other TH functions
mkMigrate :: String -> [UnboundEntityDef] -> Q [Dec] Source #
Creates a single function to perform all migrations for the entities defined here. One thing to be aware of is dependencies: if you have entities with foreign references, make sure to place those definitions after the entities they reference.
In persistent-2.13.0.0
, this was changed to *ignore* the input entity def
list, and instead defer to mkEntityDefList
to get the correct entities.
This avoids problems where the QuasiQuoter is unable to know what the right
reference types are. This sets mkPersist
to be the "single source of truth"
for entity definitions.
migrateModels :: [EntityDef] -> Migration Source #
The basic function for migrating models, no Template Haskell required.
It's probably best to use this in concert with mkEntityDefList
, and then
call migrateModels
with the result from that function.
share [mkPersist sqlSettings, mkEntityDefList "entities"] [persistLowerCase| ... |]
migrateAll = migrateModels
entities
The function mkMigrate
currently implements exactly this behavior now. If
you're splitting up the entity definitions into separate files, then it is
better to use the entity definition list and the concatenate all the models
together into a big list to call with migrateModels
.
module Foo where share [mkPersist s, mkEntityDefList "fooModels"] ... module Bar where share [mkPersist s, mkEntityDefList "barModels"] ... module Migration where import Foo import Bar migrateAll = migrateModels (fooModels <> barModels)
Since: 2.13.0.0
discoverEntities :: Q Exp Source #
Splice in a list of all EntityDef
in scope. This is useful when running
mkPersist
to ensure that all entity definitions are available for setting
foreign keys, and for performing migrations with all entities available.
mkPersist
has the type MkPersistSettings -> [EntityDef] -> DecsQ
. So, to
account for entities defined elsewhere, you'll mappend $(discoverEntities)
.
For example,
share [ mkPersistWith sqlSettings $(discoverEntities) ] [persistLowerCase| ... |]
Likewise, to run migrations with all entity instances in scope, you'd write:
migrateAll = migrateModels $(discoverEntities)
Note that there is some odd behavior with Template Haskell and splicing
groups. If you call discoverEntities
in the same module that defines
PersistEntity
instances, you need to ensure they are in different top-level
binding groups. You can write $(pure [])
at the top level to do this.
-- Foo and Bar both export an instance of PersistEntity
import Foo
import Bar
-- Since Foo and Bar are both imported, discoverEntities can find them here.
mkPersistWith sqlSettings $(discoverEntities) [persistLowerCase|
User
name Text
age Int
|]
-- onlyFooBar is defined in the same 'top level group' as the above generated
-- instance for User, so it isn't present in this list.
onlyFooBar :: [EntityDef]
onlyFooBar = $(discoverEntities)
-- We can manually create a new binding group with this, which splices an
-- empty list of declarations in.
$(pure [])
-- fooBarUser is able to see the User
instance.
fooBarUser :: [EntityDef]
fooBarUser = $(discoverEntities)
Since: 2.13.0.0
:: String | The name that will be given to the |
-> [UnboundEntityDef] | |
-> Q [Dec] |
Creates a declaration for the [
from the EntityDef
]persistent
schema. This is necessary because the Persistent QuasiQuoter is unable
to know the correct type of ID fields, and assumes that they are all
Int64.
Provide this in the list you give to share
, much like
.mkMigrate
share
[mkMigrate
"migrateAll",mkEntityDefList
"entityDefs"] [...]
Since: 2.7.1
share :: [[a] -> Q [Dec]] -> [a] -> Q [Dec] Source #
Apply the given list of functions to the same EntityDef
s.
This function is useful for cases such as:
share [mkEntityDefList
"myDefs",mkPersist
sqlSettings] [persistLowerCase
| -- ... |]
If you only have a single function, though, you don't need this. The following is redundant:
share
[mkPersist
sqlSettings
] [persistLowerCase
| -- ... |]
Most functions require a full [
, which can be provided
using EntityDef
]$(
for all entites in scope, or defining
discoverEntities
)mkEntityDefList
to define a list of entities from the given block.
derivePersistField :: String -> Q [Dec] Source #
Automatically creates a valid PersistField
instance for any datatype
that has valid Show
and Read
instances. Can be very convenient for
Enum
types.
derivePersistFieldJSON :: String -> Q [Dec] Source #
Automatically creates a valid PersistField
instance for any datatype
that has valid ToJSON
and FromJSON
instances. For a datatype T
it
generates instances similar to these:
instance PersistField T where toPersistValue = PersistByteString . L.toStrict . encode fromPersistValue = (left T.pack) . eitherDecodeStrict' <=< fromPersistValue instance PersistFieldSql T where sqlType _ = SqlString
persistFieldFromEntity :: MkPersistSettings -> UnboundEntityDef -> Q [Dec] Source #
Produce code similar to the following:
instance PersistEntity e => PersistField e where toPersistValue = entityToPersistValueHelper fromPersistValue = entityFromPersistValueHelper ["col1", "col2"] sqlType _ = SqlString
Internal
parseReferences :: PersistSettings -> Text -> Q Exp Source #
Calls parse
to Quasi.parse individual entities in isolation
afterwards, sets references to other entities
In 2.13.0.0, this was changed to splice in [
instead of UnboundEntityDef
][
.EntityDef
]
Since: 2.5.3
:: [EntityDef] | A list of Since: 2.13.0.0 |
-> [UnboundEntityDef] | |
-> [UnboundEntityDef] |
Takes a list of (potentially) independently defined entities and properly
links all foreign keys to reference the right EntityDef
, tying the knot
between entities.
Allows users to define entities indepedently or in separate modules and then
fix the cross-references between them at runtime to create a Migration
.
Since: 2.7.2
fieldError :: Text -> Text -> Text -> Text Source #
Render an error message based on the tableName
and fieldName
with
the provided message.
Since: 2.8.2
class PersistEntity record => AtLeastOneUniqueKey record where Source #
This class is used to ensure that functions requring at least one
unique key are not called with records that have 0 unique keys. The
quasiquoter automatically writes working instances for appropriate
entities, and generates TypeError
instances for records that have
0 unique keys.
Since: 2.10.0
requireUniquesP :: record -> NonEmpty (Unique record) Source #
class PersistEntity record => OnlyOneUniqueKey record where Source #
This class is used to ensure that upsert
is only called on records
that have a single Unique
key. The quasiquoter automatically generates
working instances for appropriate records, and generates TypeError
instances for records that have 0 or multiple unique keys.
Since: 2.10.0
onlyUniqueP :: record -> Unique record Source #
pkNewtype :: MkPersistSettings -> UnboundEntityDef -> Bool Source #
Returns True
if the key definition has less than 2 fields.
Since: 2.11.0.0