mirror of
https://github.com/khibino/haskell-relational-record.git
synced 2024-12-12 12:09:08 +03:00
Add TH functions to define Table type.
This commit is contained in:
parent
d6ace60288
commit
b745f31f7b
@ -1,30 +1,69 @@
|
|||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
|
||||||
module Database.Relational.Query.TH (
|
module Database.Relational.Query.TH (
|
||||||
VarName, inlineQuery
|
defineTable, defineTableDefault,
|
||||||
|
defineRecordAndTableDefault,
|
||||||
|
|
||||||
|
inlineQuery
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Data.Char (toUpper, toLower)
|
||||||
|
|
||||||
import Language.Haskell.TH
|
import Language.Haskell.TH
|
||||||
(Q, reify, Info (VarI), TypeQ, Type (AppT, ConT),
|
(Q, reify, Info (VarI), TypeQ, Type (AppT, ConT),
|
||||||
Dec, sigD, valD, varP, normalB, stringE, listE)
|
Dec, sigD, valD, varP, normalB, stringE, listE, varE)
|
||||||
import Language.Haskell.TH.Name.CamelCase (VarName, varName)
|
import Language.Haskell.TH.Name.CamelCase
|
||||||
|
(VarName, varName, ConName, varNameWithPrefix, varCamelcaseName)
|
||||||
import Language.Haskell.TH.Name.Extra (compileError, simpleValD)
|
import Language.Haskell.TH.Name.Extra (compileError, simpleValD)
|
||||||
|
|
||||||
|
import Database.Record.TH (recordTypeDefault, defineRecordDefault)
|
||||||
|
|
||||||
import Database.Relational.Query.Table (Table)
|
import Database.Relational.Query.Table (Table)
|
||||||
import qualified Database.Relational.Query.Table as Table
|
import qualified Database.Relational.Query.Table as Table
|
||||||
import Database.Relational.Query.Relation (Relation, toSQL)
|
import Database.Relational.Query.Relation (Relation, toSQL, fromTable)
|
||||||
import Database.Relational.Query.Type (Query, unsafeTypedQuery)
|
import Database.Relational.Query.Type (Query, unsafeTypedQuery)
|
||||||
|
|
||||||
defineTableInfo :: VarName
|
|
||||||
-> TypeQ
|
tableSQL :: String -> String -> String
|
||||||
-> String
|
tableSQL schema table = map toUpper schema ++ '.' : map toLower table
|
||||||
-> [String]
|
|
||||||
-> Int
|
defineTable :: VarName -- ^ Table declaration variable name
|
||||||
-> Q [Dec]
|
-> VarName -- ^ Relation declaration variable name
|
||||||
defineTableInfo tableVar' recordType table fields width = do
|
-> TypeQ -- ^ Record type
|
||||||
|
-> String -- ^ Table name in SQL ex. FOO_SCHEMA.table0
|
||||||
|
-> [String] -- ^ Column names
|
||||||
|
-> Q [Dec] -- ^ Table and Relation declaration
|
||||||
|
defineTable tableVar' relVar' recordType table columns = do
|
||||||
let tableVar = varName tableVar'
|
let tableVar = varName tableVar'
|
||||||
simpleValD tableVar [t| Table $(recordType) |]
|
tableV <- simpleValD tableVar [t| Table $(recordType) |]
|
||||||
[| Table.table $(stringE table) $(listE $ map stringE fields) |]
|
[| Table.table $(stringE table) $(listE $ map stringE columns) |]
|
||||||
|
let relVar = varName relVar'
|
||||||
|
relV <- simpleValD relVar [t| Relation $(recordType) |]
|
||||||
|
[| fromTable $(varE tableVar) |]
|
||||||
|
return $ tableV ++ relV
|
||||||
|
|
||||||
|
defineTableDefault :: String -- ^ Schema name
|
||||||
|
-> String -- ^ Table name
|
||||||
|
-> [String] -- ^ Column names
|
||||||
|
-> Q [Dec] -- ^ Result declarations
|
||||||
|
defineTableDefault schema table columns =
|
||||||
|
defineTable
|
||||||
|
(table `varNameWithPrefix` "tableOf")
|
||||||
|
(varCamelcaseName table)
|
||||||
|
(recordTypeDefault table)
|
||||||
|
(tableSQL schema table)
|
||||||
|
columns
|
||||||
|
|
||||||
|
defineRecordAndTableDefault :: TypeQ -- ^ SQL value type
|
||||||
|
-> String -- ^ Schema name
|
||||||
|
-> String -- ^ Table name
|
||||||
|
-> [(String, TypeQ)] -- ^ Column names and types
|
||||||
|
-> [ConName] -- ^ Record derivings
|
||||||
|
-> Q [Dec] -- ^ Result declarations
|
||||||
|
defineRecordAndTableDefault sqlValueType schema table columns drives = do
|
||||||
|
recDs <- defineRecordDefault sqlValueType table columns drives
|
||||||
|
tableDs <- defineTableDefault schema table (map fst columns)
|
||||||
|
return $ recDs ++ tableDs
|
||||||
|
|
||||||
inlineQuery :: VarName -> Relation r -> VarName -> TypeQ -> Q [Dec]
|
inlineQuery :: VarName -> Relation r -> VarName -> TypeQ -> Q [Dec]
|
||||||
inlineQuery relVar' rel qVar' paramType = do
|
inlineQuery relVar' rel qVar' paramType = do
|
||||||
|
Loading…
Reference in New Issue
Block a user