| Safe Haskell | None | 
|---|
Database.Persist.TH
Contents
Description
This module provides utilities for creating backends. Regular users do not need to use this module.
- persistWith :: PersistSettings -> QuasiQuoter
- persistUpperCase :: QuasiQuoter
- persistLowerCase :: QuasiQuoter
- persistFileWith :: PersistSettings -> FilePath -> Q Exp
- persist :: QuasiQuoter
- persistFile :: FilePath -> Q Exp
- mkPersist :: MkPersistSettings -> [EntityDef] -> Q [Dec]
- data  MkPersistSettings  = MkPersistSettings {- mpsBackend :: Type
 
- sqlSettings :: MkPersistSettings
- mkMigrate :: String -> [EntityDef] -> Q [Dec]
- mkSave :: String -> [EntityDef] -> Q [Dec]
- mkDeleteCascade :: [EntityDef] -> Q [Dec]
- share :: [[EntityDef] -> Q [Dec]] -> [EntityDef] -> Q [Dec]
- derivePersistField :: String -> Q [Dec]
- persistFieldFromEntity :: EntityDef -> Q [Dec]
- share2 :: ([EntityDef] -> Q [Dec]) -> ([EntityDef] -> Q [Dec]) -> [EntityDef] -> Q [Dec]
Parse entity defs
persistWith :: PersistSettings -> QuasiQuoterSource
Converts a quasi-quoted syntax into a list of entity definitions, to be used as input to the template haskell generation code (mkPersist).
persistFileWith :: PersistSettings -> FilePath -> Q ExpSource
Same as persistWith, but uses an external file instead of a
 quasiquotation.
Deprecated synonyms
Deprecated: Please use persistUpperCase instead.
Deprecate synonym for persistUpperCase.
persistFile :: FilePath -> Q ExpSource
Deprecated function. Equivalent to persistFileWith upperCaseSettings.
Turn EntityDefs into types
mkPersist :: MkPersistSettings -> [EntityDef] -> Q [Dec]Source
Create data types and appropriate PersistEntity instances for the given
 EntityDefs. Works well with the persist quasi-quoter.
data MkPersistSettings Source
Settings to be passed to the mkPersist function.
Constructors
| MkPersistSettings | |
| Fields 
 | |
sqlSettings :: MkPersistSettingsSource
Use the SqlPersist backend.
Various other TH functions
mkMigrate :: String -> [EntityDef] -> 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.
mkDeleteCascade :: [EntityDef] -> Q [Dec]Source
Generate a DeleteCascade instance for the given EntityDefs.
share :: [[EntityDef] -> Q [Dec]] -> [EntityDef] -> Q [Dec]Source
Apply the given list of functions to the same EntityDefs.
This function is useful for cases such as:
>>>share [mkSave "myDefs", mkPersist sqlSettings] [persistLowerCase|...|]
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.
persistFieldFromEntity :: EntityDef -> Q [Dec]Source
produce code similar to the following:
instance PersistEntity e => PersistField e where toPersistValue = PersistMap $ zip columNames (map toPersistValue . toPersistFields) fromPersistValue (PersistMap o) = fromPersistValues $ map ((_,v) -> casefromPersistValue v of Left e -> error e Right r -> r) o fromPersistValue x = Left $ Expected PersistMap, received: ++ show x sqlType _ = SqlString