Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- deriveEsqueletoRecord :: Name -> Q [Dec]
- deriveEsqueletoRecordWith :: DeriveEsqueletoRecordSettings -> Name -> Q [Dec]
- data DeriveEsqueletoRecordSettings = DeriveEsqueletoRecordSettings {
- sqlNameModifier :: String -> String
- sqlFieldModifier :: String -> String
- defaultDeriveEsqueletoRecordSettings :: DeriveEsqueletoRecordSettings
Documentation
deriveEsqueletoRecord :: Name -> Q [Dec] Source #
Takes the name of a Haskell record type and creates a variant of that
record prefixed with Sql
which can be used in esqueleto expressions. This
reduces the amount of pattern matching on large tuples required to interact
with data extracted with esqueleto.
Note that because the input record and the Sql
-prefixed record share field
names, the {-# LANGUAGE DuplicateRecordFields #-}
extension is required in
modules that use deriveEsqueletoRecord
. Additionally, the {-# LANGUAGE
TypeApplications #-}
extension is required for some of the generated code.
Given the following record:
data MyRecord = MyRecord { myName ::Text
, myAge ::Maybe
Int
, myUser ::Entity
User , myAddress ::Maybe
(Entity
Address) }
$(
will generate roughly the following code:deriveEsqueletoRecord
''MyRecord)
data SqlMyRecord = SqlMyRecord { myName ::SqlExpr
(Value
Text) , myAge ::SqlExpr
(Value
(Maybe
Int)) , myUser ::SqlExpr
(Entity
User) , myAddress ::SqlExpr
(Maybe
(Entity
Address)) } instanceSqlSelect
SqlMyRecord MyRecord wheresqlSelectCols
identInfo SqlMyRecord { myName = myName , myAge = myAge , myUser = myUser , myAddress = myAddress } =sqlSelectCols
identInfo (myName :& myAge :& myUser :& myAddress)sqlSelectColCount
_ =sqlSelectColCount
(Proxy
@( (SqlExpr
(Value
Text)) :& (SqlExpr
(Value
(Maybe
Int))) :& (SqlExpr
(Entity
User)) :& (SqlExpr
(Maybe
(Entity
Address)))))sqlSelectProcessRow
columns =first
((fromString
"Failed to parse MyRecord: ") <>) (evalStateT
process columns) where process = doValue
myName <-takeColumns
@(SqlExpr
(Value
Text))Value
myAge <-takeColumns
@(SqlExpr
(Value
(Maybe
Int))) myUser <-takeColumns
@(SqlExpr
(Entity
User)) myAddress <-takeColumns
@(SqlExpr
(Maybe
(Entity
Address)))pure
MyRecord { myName = myName , myAge = myAge , myUser = myUser , myAddress = myAddress }
Then, we could write a selection function to use the record in queries:
getMyRecord ::SqlPersistT
IO
[MyRecord] getMyRecord =select
myRecordQuery myRecordQuery ::SqlQuery
SqlMyRecord myRecordQuery = do user:&
address <-from
$
table
@User `leftJoin
`table
@Address `on
` (do \(user:&
address) -> user^.
#address==.
address?.
#id)pure
SqlMyRecord { myName =castString
$
user^.
#firstName , myAge =val
10 , myUser = user , myAddress = address }
Since: 3.5.6.0
deriveEsqueletoRecordWith :: DeriveEsqueletoRecordSettings -> Name -> Q [Dec] Source #
Takes the name of a Haskell record type and creates a variant of that record based on the supplied settings which can be used in esqueleto expressions. This reduces the amount of pattern matching on large tuples required to interact with data extracted with esqueleto.
This is a variant of deriveEsqueletoRecord
which allows you to avoid the
use of {-# LANGUAGE DuplicateRecordFields #-}
, by configuring the
DeriveEsqueletoRecordSettings
used to generate the SQL record.
Since: 3.5.8.0
data DeriveEsqueletoRecordSettings Source #
Codegen settings for deriveEsqueletoRecordWith
.
Since: 3.5.8.0
DeriveEsqueletoRecordSettings | |
|
defaultDeriveEsqueletoRecordSettings :: DeriveEsqueletoRecordSettings Source #
The default codegen settings for deriveEsqueletoRecord
.
These defaults will cause you to require {-# LANGUAGE DuplicateRecordFields #-}
in certain cases (see deriveEsqueletoRecord
.) If you don't want to do this,
change the value of sqlFieldModifier
so the field names of the generated SQL
record different from those of the Haskell record.
Since: 3.5.8.0