hasql-th-0.3: Template Haskell utilities for Hasql

Safe HaskellNone
LanguageHaskell2010

Hasql.TH

Contents

Synopsis

Statements

Quasiquoters in this category produce Hasql Statements, checking the correctness of SQL at compile-time.

To extract the information about parameters and results of the statement, the quoter requires you to explicitly specify the Postgres types for placeholders and results.

Here's an example of how to use it:

selectUserDetails :: Statement Int32 (Maybe (Text, Text, Maybe Text))
selectUserDetails =
  [maybeStatement|
    select name :: text, email :: text, phone :: text?
    from "user"
    where id = $1 :: int4
    |]

Nullability

As you might have noticed in the example, we introduce one change to the Postgres syntax in the way the typesignatures are parsed: we interpret question-marks in them as specification of nullability. Here's more examples of that:

>>> :t [singletonStatement| select a :: int4? |]
...
  :: Statement () (Maybe Int32)

You can use it to specify the nullability of array elements:

>>> :t [singletonStatement| select a :: int4[]? |]
...
  :: Data.Vector.Generic.Base.Vector v Int32 =>
     Statement () (Maybe (v Int32))

And of arrays themselves:

>>> :t [singletonStatement| select a :: int4?[]? |]
...
  :: Data.Vector.Generic.Base.Vector v (Maybe Int32) =>
     Statement () (Maybe (v (Maybe Int32)))

Row-parsing statements

singletonStatement :: QuasiQuoter Source #

Statement producing exactly one result row.

Will raise UnexpectedAmountOfRows error if it's any other.

Examples

>>> :t [singletonStatement|select 1 :: int2|]
... :: Statement () Int16
>>> :{
  :t [singletonStatement|
       insert into "user" (email, name)
       values ($1 :: text, $2 :: text)
       returning id :: int4
       |]
:}
...
... :: Statement (Text, Text) Int32

Incorrect SQL:

>>> :t [singletonStatement|elect 1|]
...
  |
1 | elect 1
  | ^^^^^^
unexpected "elect "
...

maybeStatement :: QuasiQuoter Source #

Statement producing one row or none.

>>> :t [maybeStatement|select 1 :: int2|]
... :: Statement () (Maybe Int16)

vectorStatement :: QuasiQuoter Source #

Statement producing a vector of rows.

>>> :t [vectorStatement|select 1 :: int2|]
... :: Statement () (Vector Int16)

foldStatement :: QuasiQuoter Source #

Function from Fold over rows to a statement producing the result of folding. Use this when you need to aggregate rows customly.

>>> :t [foldStatement|select 1 :: int2|]
... :: Fold Int16 b -> Statement () b

Row-ignoring statements

resultlessStatement :: QuasiQuoter Source #

Statement producing no results.

>>> :t [resultlessStatement|insert into "user" (name, email) values ($1 :: text, $2 :: text)|]
...
... :: Statement (Text, Text) ()

rowsAffectedStatement :: QuasiQuoter Source #

Statement counting the rows it affects.

>>> :t [rowsAffectedStatement|delete from "user" where password is null|]
...
... :: Statement () Int64

SQL ByteStrings

ByteString-producing quasiquoters.

For now they perform no compile-time checking.

uncheckedSql :: QuasiQuoter Source #

Quoter of a multiline Unicode SQL string, which gets converted into a format ready to be used for declaration of statements.

uncheckedSqlFile :: QuasiQuoter Source #

Read an SQL-file, containing multiple statements, and produce an expression of type ByteString.

Allows to store plain SQL in external files and read it at compile time.

E.g.,

migration1 :: Hasql.Session.Session ()
migration1 = Hasql.Session.sql [uncheckedSqlFile|migrations/1.sql|]