postgresql-query-1.0.1: Sql interpolating quasiquote plus some kind of primitive ORM using it

Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.Query.TH

Contents

Synopsis

Deriving instances

deriveFromRow :: Name -> Q [Dec] Source

Derive FromRow instance. i.e. you have type like that

data Entity = Entity
              { eField :: Text
              , eField2 :: Int
              , efield3 :: Bool }

then deriveFromRow will generate this instance: instance FromRow Entity where

instance FromRow Entity where
    fromRow = Entity
              <$> field
              <*> field
              <*> field

Datatype must have just one constructor with arbitrary count of fields

deriveToRow :: Name -> Q [Dec] Source

derives ToRow instance for datatype like

data Entity = Entity
              { eField :: Text
              , eField2 :: Int
              , efield3 :: Bool }

it will derive instance like that:

instance ToRow Entity where
     toRow (Entity e1 e2 e3) =
         [ toField e1
         , toField e2
         , toField e3 ]

Embedding sql files

embedSql Source

Arguments

:: String

File path

-> Q Exp 

Deprecated: use sqlExpEmbed instead

sqlFile Source

Arguments

:: String

sql file pattern

-> Q Exp 

Deprecated: use sqlExpFile instead

Sql string interpolation

sqlExp :: QuasiQuoter Source

Maybe the main feature of all library. Quasiquoter which builds SqlBuilder from string query. Removes line comments and block comments (even nested) and sequences of spaces. Correctly works handles string literals and quoted identifiers. Here is examples of usage

>>> let name = "name"
>>> let val = "some 'value'"
>>> runSqlBuilder c [sqlExp|SELECT * FROM tbl WHERE ^{mkIdent name} = #{val}|]
"SELECT * FROM tbl WHERE \"name\" = 'some ''value'''"

And more comples example:

>>> let name = Just "name"
>>> let size = Just 10
>>> let active = Nothing :: Maybe Bool
>>> let condlist = catMaybes [ fmap (\a -> [sqlExp|name = #{a}|]) name, fmap (\a -> [sqlExp|size = #{a}|]) size, fmap (\a -> [sqlExp|active = #{a}|]) active]
>>> let cond = if L.null condlist then mempty else [sqlExp| WHERE ^{mconcat $ L.intersperse " AND " $ condlist} |]
>>> runSqlBuilder c [sqlExp|SELECT *   FROM tbl ^{cond} -- line comment|]
"SELECT * FROM tbl  WHERE name = 'name' AND size = 10  "

sqlExpEmbed Source

Arguments

:: String

file path

-> Q Exp

Expression of type SqlBuilder

Embed sql template and perform interpolation

let name = "name"
    foo = "bar"
    query = $(sqlExpEmbed "sqlfoobar.sql") -- using foo and bar inside

sqlExpFile :: String -> Q Exp Source

Just like sqlExpEmbed but uses pattern instead of file name. So, code

let query = $(sqlExpFile "foo/bar")

is just the same as

let query = $(sqlExpEmbed "sqlfoobar.sql")

This function inspired by Yesod's widgetFile