haskelldb-th-1.2: Template Haskell utilities for HaskellDB.Source codeContentsIndex
Database.HaskellDB.CodeGen
Contents
Field definition.
Table definition.
Debugging utilities.
Record creation (for projection).
Description
HaskellDB is a great library for writing type-safe SQL queries. That type safety comes with a significant boilerplate overhead, though. This library provides utilities that help reduce that boilerplate by generating the definitions, types and instances that HaskellDB expects to work with. It also provides some functions for building records for projections which otherwise can be quite cumbersome.
Synopsis
mkField :: String -> TypeQ -> Q [Dec]
mkFieldWithName :: String -> String -> TypeQ -> Q [Dec]
mkDBDirectField :: String -> TypeQ -> Q [Dec]
mkDBDirectTable :: String -> [(String, TypeQ)] -> Q [Dec]
mkDBDirectTableWithName :: String -> String -> [(String, TypeQ)] -> Q [Dec]
mkDBDirectTableType :: String -> [(Name, TypeQ)] -> Q [Dec]
printQ :: Show a => Q a -> IO ()
class Ppr a
mkRecord :: [(Name, [Name])] -> ExpQ
Field definition.
mkFieldSource
:: StringName to base field
-> TypeQThe type of the field.
-> Q [Dec]

Creates a compile-time field declaration. The name given will be used to create the type and the name of the field returned. It will also be used to create a field nameField function which can be used to place the field in a projection.

For example, mkField "fooBar" [t|Int|] produces the following declarations:

 data FooBar = FooBar
 instance FieldTag FooBar where fieldName _ = "fooBar"
 fooBarField :: Attr FooBar Int
 fooBarField = mkAttr FooBar

mkField "Bar_Foo" [t|Bool|] would produce:

 data Bar_Foo = Bar_Foo
 instance FieldTag Bar_Foo where fieldName _ = "bar_Foo"
 bar_fooField :: Attr Bar_Foo Bool
 bar_fooField = mkAttr Bar_Foo
mkFieldWithNameSource
:: StringtypN - Name of the type representing the field. Must be a legal type name.
-> StringColumn name for the field.
-> TypeQType of the field.
-> Q [Dec]

Creates a compile time field declaration using the given arguments for the type and column name of the field. The typN argument is used to produce the field nameField function which can be used to add the field to a projection.

For example, mkFieldWithName "FooBar" "foo_bar" [t|Int|] gives:

 data FooBar = FooBar
 instance FieldTag FooBar where fieldName _ = "foo_bar"
 fooBarField :: Attr FooBar Int
 fooBarField = mkAttr FooBar

Note that an error will occur if typN is not a proper type/constructor name.

mkDBDirectFieldSource
:: StringcolName - column name. Will be used for a type and function name (with appropriate casing), so must be a legal name.
-> TypeQtypeQ - The type of the field.
-> Q [Dec]

Creates a field definition in the style DBDirect uses. The colName argument is used to create the data definition, type synonym, and field function. The typeQ argument specifies the type of the field.

For example, mkDBDirectField "fooBar" [t|Bool|] will produce:

 data FooBar = FooBar
 instance FieldTag FooBar where fieldName _ = "fooBar"
 fooBar :: Attr FooBar Bool
 fooBar = mkAttr FooBar
Table definition.
mkDBDirectTableSource
:: StringName of the table. Will be used to create the table type synonym and table creation function (with appropriate casing), so must be a legal name
-> [(String, TypeQ)]
-> Q [Dec]

Creates definitions for a table and all its fields in the style of DBDirect. Takes a table name and a list of fields (as types). Generates a table type and a function to construct the table. The function will be the tablename in lower case. The type alias will be the table name with the first character capitalized.

For example:

 mkDBDirectTable "Table1" [("Col1", [t|Int|])
                          , ("Col2", [t|Bool|])]

Will produce

 type Table1 = (RecCons Col1 (Expr Int)
                (RecCons Col2 (Expr Bool)))
 
 table1 :: Table Table1
 table1 = baseTable "Table1" $
          hdbMakeEntry Col1 #
          hdbMakeEntry Col2

 data Col1 = Col1
 instance FieldTag Col1 where fieldName _ = "col1"
 col1 :: Attr Col1 Int
 col1 = mkAttr Col1

 data Col2 = Col2
 instance FieldTag Col2 where fieldName _ = "col2"
 col2 :: Attr Col2 Int
 col2 = mkAttr Col2
mkDBDirectTableWithNameSource
:: StringName of the table type to create. Will be cased properly but must be a legal name.
-> StringName of table to use in actual SQL generated.
-> [(String, TypeQ)]
-> Q [Dec]
Creates definitions for a table and all its fields in the style of DBDirect. Takes a table name and a list of fields (as types). Generates a table type and a function to construct the table. The function will be the tablename in lower case. The type alias will be the table name with the first character capitalized. See mkDBirectTable for an example, as that function calls this one.
mkDBDirectTableTypeSource
:: StringName of the type synonym. Must be a legal name and properly cased.
-> [(Name, TypeQ)]List of fields in the table. Must be legal, properly cased fields.
-> Q [Dec]The type synonym declaration.
Creates a type synonym for a table with the name given, using the list of fields given. See mkDBDirectField for an example, as that function calls this one to create the type signature.
Debugging utilities.
printQ :: Show a => Q a -> IO ()Source
class Ppr a Source
show/hide Instances
Record creation (for projection).
mkRecord :: [(Name, [Name])] -> ExpQSource

Create a record from the list of tables and fields given. The first element of each tuple is a table. The second is a list of fields from that table which will be in the new record. The record will be constructed in the order of tables and fields given.

This is a Template Haskell function which must be spliced in and is intended to use the ' (quote) facility for capturing names. An example:

 import Status_v (Status_v, status_v)
 import qualified Status_v as Status_v

 import Dtls_v (Dtls_v, dtls_v)
 import qualified Dtls_v as Dtls_v

 
  qry = do
    status <- table status_v;
    dtls <- table dtls_v;
    project $(mkRecord [('dtls, ['Dtls_v.desc
                         , 'Dtls_v.hdr_id
                         , 'Dtls_v.prt_id
                         , 'Dtls_v.dtl_id])
                       ,('status, ['Status_v.stat_nbr])])

The type of qry is then

          (RecCons Dtls_v.Desc (Expr (Maybe BStr40))
          (RecCons Dtls_v.Hdr_id (Expr (Maybe Int))
          (RecCons Dtls_v.Prt_id (Expr (Maybe BStr30))
          (RecCons Dtls_v.Dtl_id (Expr (Maybe Int))
          (RecCons Status_v.Stat_nbr (Expr (Maybe Int)) RecNil))))))

If other fields need to be added to the record, they must come before the call to mkRecord:

    project $ filtered << someTable ! someField #
              $(mkRecord [('dtls, ['Dtls_v.prt_desc
                                    , 'Dtls.hdr_id
                                    , 'Dtls.prt_id
                                    , 'Dtls.dtl_id])
                          ,('status, ['Status_v.stat_nbr])])
Produced by Haddock version 2.6.0