| Copyright | 2013 Kei Hibino |
|---|---|
| License | BSD3 |
| Maintainer | ex8k.hibino@gmail.com |
| Stability | experimental |
| Portability | unknown |
| Safe Haskell | None |
| Language | Haskell2010 |
Database.Record.TH
Contents
Description
This module defines templates for Haskell record type and type class instances to map between list of untyped SQL type and Haskell record type.
- defineRecord :: TypeQ -> (VarName, VarName) -> ConName -> [(VarName, TypeQ)] -> [Name] -> Q [Dec]
- defineRecordWithConfig :: TypeQ -> NameConfig -> String -> String -> [(String, TypeQ)] -> [Name] -> Q [Dec]
- derivingEq :: Name
- derivingShow :: Name
- derivingRead :: Name
- derivingData :: Name
- derivingTypeable :: Name
- defineHasColumnConstraintInstance :: TypeQ -> TypeQ -> Int -> Q [Dec]
- defineHasPrimaryConstraintInstanceDerived :: TypeQ -> Q [Dec]
- defineHasPrimaryKeyInstance :: TypeQ -> [Int] -> Q [Dec]
- defineHasNotNullKeyInstance :: TypeQ -> Int -> Q [Dec]
- defineRecordType :: ConName -> [(VarName, TypeQ)] -> [Name] -> Q [Dec]
- defineRecordTypeWithConfig :: NameConfig -> String -> String -> [(String, TypeQ)] -> [Name] -> Q [Dec]
- makeRecordPersistableWithSqlType :: TypeQ -> (VarName, VarName) -> (TypeQ, ExpQ) -> Int -> Q [Dec]
- makeRecordPersistableWithSqlTypeWithConfig :: TypeQ -> NameConfig -> String -> String -> Int -> Q [Dec]
- makeRecordPersistableWithSqlTypeDefault :: TypeQ -> String -> String -> Int -> Q [Dec]
- makeRecordPersistableWithSqlTypeFromDefined :: TypeQ -> (VarName, VarName) -> Name -> Q [Dec]
- makeRecordPersistableWithSqlTypeDefaultFromDefined :: TypeQ -> Name -> Q [Dec]
- defineColumnOffsets :: ConName -> [TypeQ] -> Q [Dec]
- recordWidthTemplate :: TypeQ -> ExpQ
- defineRecordParser :: TypeQ -> VarName -> (TypeQ, ExpQ) -> Int -> Q [Dec]
- defineRecordPrinter :: TypeQ -> VarName -> (TypeQ, ExpQ) -> Int -> Q [Dec]
- definePersistableInstance :: TypeQ -> TypeQ -> VarName -> VarName -> Int -> Q [Dec]
- reifyRecordType :: Name -> Q ((TypeQ, ExpQ), (Maybe [Name], [TypeQ]))
- data NameConfig
- defaultNameConfig :: NameConfig
- recordTypeName :: NameConfig -> String -> String -> ConName
- recordType :: NameConfig -> String -> String -> TypeQ
- columnOffsetsVarNameDefault :: Name -> VarName
- persistableFunctionNamesDefault :: Name -> (VarName, VarName)
- deriveNotNullType :: TypeQ -> Q [Dec]
Generate all templates about record
Arguments
| :: TypeQ | SQL value type |
| -> (VarName, VarName) | Constructor function name and decompose function name |
| -> ConName | Record type name |
| -> [(VarName, TypeQ)] | Column schema |
| -> [Name] | Record derivings |
| -> Q [Dec] | Result declarations |
All templates for record type.
defineRecordWithConfig Source #
Arguments
| :: TypeQ | SQL value type |
| -> NameConfig | name rule config |
| -> String | Schema name |
| -> String | Table name |
| -> [(String, TypeQ)] | Column names and types |
| -> [Name] | Record derivings |
| -> Q [Dec] | Result declarations |
All templates for record type with configured names.
Deriving class symbols
derivingEq :: Name Source #
Deprecated: Use TH quasi-quotation like ''Eq instead of this.
Name to specify deriving Eq
derivingShow :: Name Source #
Deprecated: Use TH quasi-quotation like ''Show instead of this.
Name to specify deriving Show
derivingRead :: Name Source #
Deprecated: Use TH quasi-quotation like ''Read instead of this.
Name to specify deriving Read
derivingData :: Name Source #
Deprecated: Use TH quasi-quotation like ''Data instead of this.
Name to specify deriving Data
derivingTypeable :: Name Source #
Deprecated: Use TH quasi-quotation like ''Typeable instead of this.
Name to specify deriving Typeable
Table constraint specified by key
defineHasColumnConstraintInstance Source #
Arguments
| :: TypeQ | Type which represent constraint type |
| -> TypeQ | Type constructor of record |
| -> Int | Key index which specifies this constraint |
| -> Q [Dec] | Result declaration template |
Template of HasColumnConstraint instance.
defineHasPrimaryConstraintInstanceDerived Source #
Template of HasKeyConstraint instance.
defineHasPrimaryKeyInstance Source #
Arguments
| :: TypeQ | Type constructor of record |
| -> [Int] | Key index which specifies this constraint |
| -> Q [Dec] | Declaration of primary key constraint instance |
Template of HasColumnConstraint Primary instance.
defineHasNotNullKeyInstance Source #
Arguments
| :: TypeQ | Type constructor of record |
| -> Int | Key index which specifies this constraint |
| -> Q [Dec] | Declaration of not null key constraint instance |
Template of HasColumnConstraint NotNull instance.
Record type
Arguments
| :: ConName | Name of the data type of table record type. |
| -> [(VarName, TypeQ)] | List of columns in the table. Must be legal, properly cased record columns. |
| -> [Name] | Deriving type class names. |
| -> Q [Dec] | The data type record declaration. |
Record type declaration template.
defineRecordTypeWithConfig :: NameConfig -> String -> String -> [(String, TypeQ)] -> [Name] -> Q [Dec] Source #
Record type declaration template with configured names.
Function declarations depending on SQL type
makeRecordPersistableWithSqlType Source #
Arguments
| :: TypeQ | SQL value type. |
| -> (VarName, VarName) | Constructor function name and decompose function name. |
| -> (TypeQ, ExpQ) | Record type constructor and data constructor. |
| -> Int | Count of record columns. |
| -> Q [Dec] | Result declarations. |
All templates depending on SQL value type.
makeRecordPersistableWithSqlTypeWithConfig Source #
Arguments
| :: TypeQ | SQL value type |
| -> NameConfig | name rule config |
| -> String | Schema name of database |
| -> String | Table name of database |
| -> Int | Count of record columns |
| -> Q [Dec] | Result declarations |
All templates depending on SQL value type with configured names.
makeRecordPersistableWithSqlTypeDefault Source #
Arguments
| :: TypeQ | SQL value type |
| -> String | Schema name |
| -> String | Table name |
| -> Int | Count of record columns |
| -> Q [Dec] | Result declarations |
All templates depending on SQL value type with default names.
Function declarations against defined record types
makeRecordPersistableWithSqlTypeFromDefined Source #
Arguments
| :: TypeQ | SQL value type |
| -> (VarName, VarName) | Constructor function name and decompose function name |
| -> Name | Record type constructor name |
| -> Q [Dec] | Result declarations |
All templates depending on SQL value type. Defined record type information is used.
makeRecordPersistableWithSqlTypeDefaultFromDefined Source #
All templates depending on SQL value type with default names. Defined record type information is used.
Arguments
| :: ConName | Record type constructor. |
| -> [TypeQ] | Types of record columns. |
| -> Q [Dec] | Declaration of |
Column offset array and PersistableWidth instance declaration.
Record type width expression template.
Arguments
| :: TypeQ | SQL value type. |
| -> VarName | Name of record parser. |
| -> (TypeQ, ExpQ) | Record type constructor and data constructor. |
| -> Int | Count of record columns. |
| -> Q [Dec] | Declaration of record construct function from SQL values. |
Record parser template.
Arguments
| :: TypeQ | SQL value type. |
| -> VarName | Name of record printer. |
| -> (TypeQ, ExpQ) | Record type constructor and data constructor. |
| -> Int | Count of record columns. |
| -> Q [Dec] | Declaration of record construct function from SQL values. |
Record printer template.
definePersistableInstance Source #
Arguments
| :: TypeQ | SQL value type. |
| -> TypeQ | Record type constructor. |
| -> VarName | Record parser name. |
| -> VarName | Record printer name. |
| -> Int | Count of record columns. |
| -> Q [Dec] | Instance declarations for |
Record parser and printer instance templates for converting between list of SQL type and Haskell record type.
Reify
reifyRecordType :: Name -> Q ((TypeQ, ExpQ), (Maybe [Name], [TypeQ])) Source #
Low-level reify interface for record type name.
Templates about record type name
data NameConfig Source #
NameConfig type to customize names of expanded record templates.
Instances
| Show NameConfig Source # | Dummy show instance. Handy to define show instance recursively. |
defaultNameConfig :: NameConfig Source #
Default implementation of NameConfig type
recordTypeName :: NameConfig -> String -> String -> ConName Source #
Make record type symbol name from schema name and table name in SQL
Arguments
| :: NameConfig | name rule config |
| -> String | Schema name string in SQL |
| -> String | Table name string in SQL |
| -> TypeQ | Record type constructor |
Record type constructor template from SQL table name String.
columnOffsetsVarNameDefault Source #
Variable expression of record column offset array.
persistableFunctionNamesDefault :: Name -> (VarName, VarName) Source #
Generate persistable function symbol names using default rule.