[Haskell-cafe] Help using Groundhog Template Haskell.
Andrew Myers
asm198 at gmail.com
Fri Nov 8 02:38:19 UTC 2013
Hi Cafe,
I'm trying to experiment with groundhog because I want something that I can map between arbitrary ADTs and arbitrary Schema.
Groundhog looks like exactly what I want but I'm hung up on an error coming from the mkPersist TH function. When I compile
the code below with ghc --make groundhog.hs I get this error:
groundhog.hs:23:1:
Function binding for `Database.Groundhog.Core.entityFieldChain' has no equations
When splicing a TH declaration:
I'm pretty sure it has something to do with the TransactionType not being made up of primitive types but I'm not sure
what to do about it. Can someone familiar with the library point me in the right direction?
Thanks,
Andrew Myers
{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
module Checking.Database.Groundhog where
import qualified Database.Groundhog.TH as TH
import qualified Data.Text as T
import qualified Data.Time as D
import qualified Control.Lens as L
data TransactionType = Deposit | Debt | Informational
deriving (Show, Eq, Read)
data Transaction = Transaction {
_transactionDate :: D.UTCTime
, _transactionAmount :: Double
, _transactionDescription :: T.Text
, _transactionBalanced :: Bool
, _transactionCheckNumber :: Maybe Int
, _transactionTransactionType :: TransactionType
}
deriving (Show, Read, Eq)
TH.mkPersist TH.defaultCodegenConfig [TH.groundhog|
- entity: Transaction
constructors:
- name: Transaction
fields:
- name: _transactionDate
dbName: date
exprName: DateField
- name: _transactionAmount
dbName: amount
exprName: AmountField
- name: _transactionDescription
dbName: description
exprName: DescriptionField
- name: _transactionBalanced
dbName: balanced
exprName: BalancedField
- name: _transactionCheckNumber
dbName: check_number
exprName: CheckNumberField
- name: _transactionTransactionType
dbName: transaction_type
exprName: TransactionTypeField
- entity: TransactionType
|]
More information about the Haskell-Cafe
mailing list