Skip to content

Expressions

Typing

The type of all SQL-level expressions is QGenExpr. See the query tutorial for more information.

In many cases, you'd like to type the SQL-level result of an expression without having to give explicit types for the other QGenExpr parameters. You can do this with the as_ combinator and -XTypeApplications.

The following code types the literal 1 as a Double.

as_ @Double 1

This is rarely needed, but there are a few cases where the beam types are too general for the compiler to meaningfully infer types.

Literals

  • Integer literals can be constructed using fromIntegral in the Num typeclass. This means you can also just use a Haskell integer literal as a QGenExpr in any context.
  • Rational literals can be constructed via fromRational in Rational. Regular Haskell rational literals will be automatically converted to QGenExprs.
  • Text literals can be constructed via fromString in IsString. Again, Haskell string constants will automatically be converted to QGenExprs, although you may have to provide an explicit type, as different backends support different text types natively.
  • All other literals can be constructed using the val_ function in SqlValable. This requires that there is an implementation of HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax) x for the type x in the appropriate syntax for the QGenExpr. For example, to construct a value of type Vector Int32 in the beam-postgres backend.
val_ (V.fromList [1, 2, 3 :: Int32])
  • Explicit tables can be brought to the SQL value level by using val_ as well. For example, if you have an AddressT Identity named a, val_ a :: AddressT (QGenExpr context expr s).

UTF support

All included beam backends play nicely with UTF. New backends should also support UTF, if they support syntaxes and deserializers for String or Text.

filter_ (\s -> customerFirstName s ==. "あきら") $
  all_ (customer chinookDb)
SELECT "t0"."CustomerId" AS "res0",
       "t0"."FirstName" AS "res1",
       "t0"."LastName" AS "res2",
       "t0"."Company" AS "res3",
       "t0"."Address" AS "res4",
       "t0"."City" AS "res5",
       "t0"."State" AS "res6",
       "t0"."Country" AS "res7",
       "t0"."PostalCode" AS "res8",
       "t0"."Phone" AS "res9",
       "t0"."Fax" AS "res10",
       "t0"."Email" AS "res11",
       "t0"."SupportRepId" AS "res12"
FROM "Customer" AS "t0"
WHERE ("t0"."FirstName") = ('あきら')
SELECT "t0"."CustomerId" AS "res0",
       "t0"."FirstName" AS "res1",
       "t0"."LastName" AS "res2",
       "t0"."Company" AS "res3",
       "t0"."Address" AS "res4",
       "t0"."City" AS "res5",
       "t0"."State" AS "res6",
       "t0"."Country" AS "res7",
       "t0"."PostalCode" AS "res8",
       "t0"."Phone" AS "res9",
       "t0"."Fax" AS "res10",
       "t0"."Email" AS "res11",
       "t0"."SupportRepId" AS "res12"
FROM "Customer" AS "t0"
WHERE ("t0"."FirstName")=(?);

-- With values: [SQLText "\12354\12365\12425"]

Arithmetic

Arithmetic operations that are part of the Fractional and Num classes can be used directly. For example, if a and b are QGenExprs of the same type, then a + b is a QGenExpr of the same type.

Because of the toInteger class method in Integral, QGenExprs cannot implement Integral. Nevertheless, versions of div and mod are available as div_ and mod_, respectively, having the corresponding type.

Comparison

SQL comparison is not as simple as you may think. NULL handling in particular actually makes things rather complicated. SQL comparison operators actually return a tri-state boolean, representing true, false, and unknown, which is the result when two nulls are compared. Boolean combinators (AND and OR) handle these values in different ways. Beam abstracts some of this difference away, if you ask it to.

Haskell-like comparisons

Haskell provides much more reasonable equality between potentially optional values. For example, Nothing == Nothing always! SQL does not provide a similar guarantee. However, beam can emulate Haskell-like equality in SQL using the ==. operator. This uses a CASE .. WHEN .. statement or a special operator that properly handles NULLs in your given backend. Depending on your backend, this can severely impact performance, but it's 'correct'.

For example, to find all customers living in Berlin:

filter_ (\s -> addressCity (customerAddress s) ==. val_ (Just "Berlin")) $
  all_ (customer chinookDb)
SELECT "t0"."CustomerId" AS "res0",
       "t0"."FirstName" AS "res1",
       "t0"."LastName" AS "res2",
       "t0"."Company" AS "res3",
       "t0"."Address" AS "res4",
       "t0"."City" AS "res5",
       "t0"."State" AS "res6",
       "t0"."Country" AS "res7",
       "t0"."PostalCode" AS "res8",
       "t0"."Phone" AS "res9",
       "t0"."Fax" AS "res10",
       "t0"."Email" AS "res11",
       "t0"."SupportRepId" AS "res12"
FROM "Customer" AS "t0"
WHERE ("t0"."City") IS NOT DISTINCT
  FROM ('Berlin')
SELECT "t0"."CustomerId" AS "res0",
       "t0"."FirstName" AS "res1",
       "t0"."LastName" AS "res2",
       "t0"."Company" AS "res3",
       "t0"."Address" AS "res4",
       "t0"."City" AS "res5",
       "t0"."State" AS "res6",
       "t0"."Country" AS "res7",
       "t0"."PostalCode" AS "res8",
       "t0"."Phone" AS "res9",
       "t0"."Fax" AS "res10",
       "t0"."Email" AS "res11",
       "t0"."SupportRepId" AS "res12"
FROM "Customer" AS "t0"
WHERE CASE
          WHEN (("t0"."City") IS NULL)
               AND ((?) IS NULL) THEN ?
          WHEN (("t0"."City") IS NULL)
               OR ((?) IS NULL) THEN ?
          ELSE ("t0"."City")=(?)
      END;

-- With values: [SQLText "Berlin",SQLInteger 1,SQLText "Berlin",SQLInteger 0,SQLText "Berlin"]

Notice that SQLite uses a CASE .. WHEN .. statement, while Postgres uses the IS NOT DISTINCT FROM operator.

The inequality operator is named /=., as expected. Note that both ==. and /=. return a SQL expression whose type is Bool.

SQL-like comparisons

Beam also provides equality operators that act like their underlying SQL counterparts. These operators map most directly to the SQL = and <> operators, but they require you to explicitly handle the possibility of NULLs. These operators are named ==?. and /=?. respectively.

Unlike ==. and /=., these operators return an expression of type SqlBool. SqlBool is a type that can only be manipulated as part of a SQL expression, and cannot be serialized or deserialized to/from Haskell. You need to convert it to a Bool value explicitly in order to get the result or use it with more advanced operators, such as CASE .. WHEN ...

In SQL, you can handle potentially unknown comparisons using the IS TRUE, IS NOT TRUE, IS FALSE, IS NOT FALSE, IS UNKNOWN, and IS NOT UNKNOWN operators. These are provided as the beam functions isTrue_, isNotTrue_, etc. These each take a SQL expression of type SqlBool and return one of type Bool.

For example, to join every employee and customer who live in the same city, but using SQL-like equality and making sure the comparison really is true (i.e., customers and employees who both have NULL cities will not be included).

do c <- all_ (customer chinookDb)
   e <- join_ (employee chinookDb) $ \e ->
        isTrue_ (addressCity (customerAddress c) ==?. addressCity (employeeAddress e))
   pure (c, e)
SELECT "t0"."CustomerId" AS "res0",
       "t0"."FirstName" AS "res1",
       "t0"."LastName" AS "res2",
       "t0"."Company" AS "res3",
       "t0"."Address" AS "res4",
       "t0"."City" AS "res5",
       "t0"."State" AS "res6",
       "t0"."Country" AS "res7",
       "t0"."PostalCode" AS "res8",
       "t0"."Phone" AS "res9",
       "t0"."Fax" AS "res10",
       "t0"."Email" AS "res11",
       "t0"."SupportRepId" AS "res12",
       "t1"."EmployeeId" AS "res13",
       "t1"."LastName" AS "res14",
       "t1"."FirstName" AS "res15",
       "t1"."Title" AS "res16",
       "t1"."ReportsTo" AS "res17",
       "t1"."BirthDate" AS "res18",
       "t1"."HireDate" AS "res19",
       "t1"."Address" AS "res20",
       "t1"."City" AS "res21",
       "t1"."State" AS "res22",
       "t1"."Country" AS "res23",
       "t1"."PostalCode" AS "res24",
       "t1"."Phone" AS "res25",
       "t1"."Fax" AS "res26",
       "t1"."Email" AS "res27"
FROM "Customer" AS "t0"
INNER JOIN "Employee" AS "t1" ON (("t0"."City") = ("t1"."City")) IS TRUE
SELECT "t0"."CustomerId" AS "res0",
       "t0"."FirstName" AS "res1",
       "t0"."LastName" AS "res2",
       "t0"."Company" AS "res3",
       "t0"."Address" AS "res4",
       "t0"."City" AS "res5",
       "t0"."State" AS "res6",
       "t0"."Country" AS "res7",
       "t0"."PostalCode" AS "res8",
       "t0"."Phone" AS "res9",
       "t0"."Fax" AS "res10",
       "t0"."Email" AS "res11",
       "t0"."SupportRepId" AS "res12",
       "t1"."EmployeeId" AS "res13",
       "t1"."LastName" AS "res14",
       "t1"."FirstName" AS "res15",
       "t1"."Title" AS "res16",
       "t1"."ReportsTo" AS "res17",
       "t1"."BirthDate" AS "res18",
       "t1"."HireDate" AS "res19",
       "t1"."Address" AS "res20",
       "t1"."City" AS "res21",
       "t1"."State" AS "res22",
       "t1"."Country" AS "res23",
       "t1"."PostalCode" AS "res24",
       "t1"."Phone" AS "res25",
       "t1"."Fax" AS "res26",
       "t1"."Email" AS "res27"
FROM "Customer" AS "t0"
INNER JOIN "Employee" AS "t1" ON (("t0"."City")=("t1"."City")) IS 1;

-- With values: []

Thinking of which IS .. operator to use can be confusing. If you have a default value you'd like to return in the case of an unknown comparison, use the unknownAs_ function. For example, if we want to treat unknown values as True instead (i.e, we want customers and employees who both have NULL cities to be included)

do c <- all_ (customer chinookDb)
   e <- join_ (employee chinookDb) $ \e ->
        unknownAs_ True (addressCity (customerAddress c) ==?. addressCity (employeeAddress e))
   pure (c, e)
SELECT "t0"."CustomerId" AS "res0",
       "t0"."FirstName" AS "res1",
       "t0"."LastName" AS "res2",
       "t0"."Company" AS "res3",
       "t0"."Address" AS "res4",
       "t0"."City" AS "res5",
       "t0"."State" AS "res6",
       "t0"."Country" AS "res7",
       "t0"."PostalCode" AS "res8",
       "t0"."Phone" AS "res9",
       "t0"."Fax" AS "res10",
       "t0"."Email" AS "res11",
       "t0"."SupportRepId" AS "res12",
       "t1"."EmployeeId" AS "res13",
       "t1"."LastName" AS "res14",
       "t1"."FirstName" AS "res15",
       "t1"."Title" AS "res16",
       "t1"."ReportsTo" AS "res17",
       "t1"."BirthDate" AS "res18",
       "t1"."HireDate" AS "res19",
       "t1"."Address" AS "res20",
       "t1"."City" AS "res21",
       "t1"."State" AS "res22",
       "t1"."Country" AS "res23",
       "t1"."PostalCode" AS "res24",
       "t1"."Phone" AS "res25",
       "t1"."Fax" AS "res26",
       "t1"."Email" AS "res27"
FROM "Customer" AS "t0"
INNER JOIN "Employee" AS "t1" ON (("t0"."City") = ("t1"."City")) IS NOT FALSE
SELECT "t0"."CustomerId" AS "res0",
       "t0"."FirstName" AS "res1",
       "t0"."LastName" AS "res2",
       "t0"."Company" AS "res3",
       "t0"."Address" AS "res4",
       "t0"."City" AS "res5",
       "t0"."State" AS "res6",
       "t0"."Country" AS "res7",
       "t0"."PostalCode" AS "res8",
       "t0"."Phone" AS "res9",
       "t0"."Fax" AS "res10",
       "t0"."Email" AS "res11",
       "t0"."SupportRepId" AS "res12",
       "t1"."EmployeeId" AS "res13",
       "t1"."LastName" AS "res14",
       "t1"."FirstName" AS "res15",
       "t1"."Title" AS "res16",
       "t1"."ReportsTo" AS "res17",
       "t1"."BirthDate" AS "res18",
       "t1"."HireDate" AS "res19",
       "t1"."Address" AS "res20",
       "t1"."City" AS "res21",
       "t1"."State" AS "res22",
       "t1"."Country" AS "res23",
       "t1"."PostalCode" AS "res24",
       "t1"."Phone" AS "res25",
       "t1"."Fax" AS "res26",
       "t1"."Email" AS "res27"
FROM "Customer" AS "t0"
INNER JOIN "Employee" AS "t1" ON (("t0"."City")=("t1"."City")) IS NOT 0;

-- With values: []

Quantified comparison

SQL also allows comparisons to be quantified. For example, the SQL expression a == ANY(b) evaluates to true only if one row of b is equal to a. Similarly, a > ALL(b) returns true if a > x for every x in b.

These are also supported using the ==*., /=*., <*., >*., <=*., and >=*. operators. Like their unquantified counterparts, these operators yield a QGenExpr of type Bool. Unlike the unquantified operators, the second argument of these operators is of type QQuantified. You can create a QQuantified from a QGenExpr by using the anyOf_/anyIn_ or allOf_/allIn_ functions, which correspond to the ANY and ALL syntax respectively. anyOf_ and allOf_ take Q expressions (representing a query) and anyIn_ and allIn_ take lists of expressions.

Quantified comparisons are always performed according to SQL semantics, meaning that they return values of type SqlBOol. This is because proper NULL handling with quantified comparisons cannot be expressed in a reasonable way. Use the functions described in the section above.

For example, to get all invoice lines containing tracks longer than 3 minutes:

let tracksLongerThanThreeMinutes =
      fmap trackId $
      filter_ (\t -> trackMilliseconds t >=. 180000) $
        all_ (track chinookDb)
in filter_ (\ln -> let TrackId lnTrackId = invoiceLineTrack ln
                   in unknownAs_ False (lnTrackId ==*. anyOf_ tracksLongerThanThreeMinutes)) $
     all_ (invoiceLine chinookDb)
SELECT "t0"."InvoiceLineId" AS "res0",
       "t0"."InvoiceId" AS "res1",
       "t0"."TrackId" AS "res2",
       "t0"."UnitPrice" AS "res3",
       "t0"."Quantity" AS "res4"
FROM "InvoiceLine" AS "t0"
WHERE (("t0"."TrackId") = ANY
         (SELECT "sub_t0"."TrackId" AS "res0"
          FROM "Track" AS "sub_t0"
          WHERE ("sub_t0"."Milliseconds") >= (180000))) IS TRUE

We can also supply a concrete list of values. For example to get everyone living in either Los Angeles or Manila:

filter_ (\c ->  unknownAs_ False (addressCity (customerAddress c) ==*. anyIn_ [ just_ "Los Angeles", just_ "Manila" ])) $
     all_ (customer chinookDb)
SELECT "t0"."CustomerId" AS "res0",
       "t0"."FirstName" AS "res1",
       "t0"."LastName" AS "res2",
       "t0"."Company" AS "res3",
       "t0"."Address" AS "res4",
       "t0"."City" AS "res5",
       "t0"."State" AS "res6",
       "t0"."Country" AS "res7",
       "t0"."PostalCode" AS "res8",
       "t0"."Phone" AS "res9",
       "t0"."Fax" AS "res10",
       "t0"."Email" AS "res11",
       "t0"."SupportRepId" AS "res12"
FROM "Customer" AS "t0"
WHERE (("t0"."City") = ANY (
                            VALUES ('Los Angeles'), ('Manila'))) IS TRUE

The IN predicate

You can also use in_ to use the common IN predicate.

limit_ 10 $
  filter_ (\customer -> customerFirstName customer `in_` [val_ "Johannes", val_ "Aaron", val_ "Ellie"]) $
  all_ (customer chinookDb)
SELECT "t0"."CustomerId" AS "res0",
       "t0"."FirstName" AS "res1",
       "t0"."LastName" AS "res2",
       "t0"."Company" AS "res3",
       "t0"."Address" AS "res4",
       "t0"."City" AS "res5",
       "t0"."State" AS "res6",
       "t0"."Country" AS "res7",
       "t0"."PostalCode" AS "res8",
       "t0"."Phone" AS "res9",
       "t0"."Fax" AS "res10",
       "t0"."Email" AS "res11",
       "t0"."SupportRepId" AS "res12"
FROM "Customer" AS "t0"
WHERE ("t0"."FirstName") IN ('Johannes',
                             'Aaron',
                             'Ellie')
LIMIT 10
SELECT "t0"."CustomerId" AS "res0",
       "t0"."FirstName" AS "res1",
       "t0"."LastName" AS "res2",
       "t0"."Company" AS "res3",
       "t0"."Address" AS "res4",
       "t0"."City" AS "res5",
       "t0"."State" AS "res6",
       "t0"."Country" AS "res7",
       "t0"."PostalCode" AS "res8",
       "t0"."Phone" AS "res9",
       "t0"."Fax" AS "res10",
       "t0"."Email" AS "res11",
       "t0"."SupportRepId" AS "res12"
FROM "Customer" AS "t0"
WHERE ("t0"."FirstName") IN (?,
                             ?,
                             ?)
LIMIT 10;

-- With values: [SQLText "Johannes",SQLText "Aaron",SQLText "Ellie"]

CASE .. WHEN .. ELSE .. statements

The SQL CASE .. WHEN .. ELSE construct can be used to implement a multi-way if. The corresponding beam syntax is

if_ [ cond1 `then_` result1, cond2 `then_` result2, ... ] (else_ elseResult)

where cond<n> are QGenExpr of type Bool, and result1, result2, and elseResult are QGenExprs of the same type.

Manipulating types with CAST

Oftentimes, you want to cast data between two different types. SQL provides the CAST function for this purpose. Beam exposes this functionality through the cast_ function which takes an expression and a datatype. For example, to select all line items where the first digit of the quantity is 2:

filter_ (\ln -> cast_ (invoiceLineQuantity ln) (varchar Nothing) `like_` "2%") $
  all_ (invoiceLine chinookDb)
SELECT "t0"."InvoiceLineId" AS "res0",
       "t0"."InvoiceId" AS "res1",
       "t0"."TrackId" AS "res2",
       "t0"."UnitPrice" AS "res3",
       "t0"."Quantity" AS "res4"
FROM "InvoiceLine" AS "t0"
WHERE (CAST(("t0"."Quantity") AS VARCHAR)) LIKE ('2%')
SELECT "t0"."InvoiceLineId" AS "res0",
       "t0"."InvoiceId" AS "res1",
       "t0"."TrackId" AS "res2",
       "t0"."UnitPrice" AS "res3",
       "t0"."Quantity" AS "res4"
FROM "InvoiceLine" AS "t0"
WHERE (CAST(("t0"."Quantity") AS VARCHAR)) LIKE (?);

-- With values: [SQLText "2%"]

Subqueries

When a query is used in place of an expression it's called a subquery. A query has the type Q in beam, while a beam expression has the type QGenExpr. Therefore, when using subqueries in beam, a function is needed to convert a Q (query) into a QGenExpr (expression). This function is called subquery_. Using subquery_, a query can be used where an expression is expected.

For example, suppose we wish to offer a discount on all "short" tracks, where a track is considered short if its duration is less than the average track duration for all tracks. This is achieved using an update in which the predicate contains a subquery that calculates the average track duration.

runUpdate $ update (track chinookDb)
  (\track' -> trackUnitPrice track' <-. current_ (trackUnitPrice track') / 2)
  (\track' ->
    let avgTrackDuration = aggregate_ (avg_ . trackMilliseconds) (all_ $ track chinookDb)
    in just_ (trackMilliseconds track') <. subquery_ avgTrackDuration
  )
UPDATE "Track"
SET "UnitPrice"=("UnitPrice") / ('2.0')
WHERE ("Milliseconds") < (
                            (SELECT AVG("t0"."Milliseconds") AS "res0"
                             FROM "Track" AS "t0"));
UPDATE "Track"
SET "UnitPrice"=("UnitPrice") / (?)
WHERE ("Milliseconds")<(
                          (SELECT AVG("t0"."Milliseconds") AS "res0"
                           FROM "Track" AS "t0"));

-- With values: [SQLText "2.0"];

SQL Functions and operators

SQL construct SQL standard Beam equivalent Notes
EXISTS (x) SQL92 exists_ x Here, x is any query (of type Q)
UNIQUE (x) SQL92 unique_ x See note for EXISTS (x)
DISTINCT (x) SQL99 distinct_ x See note for EXISTS (x)
SELECT .. FROM ...
as an expression (subqueries)
SQL92 subquery_ x x is an query (of type Q)
COALESCE(a, b, c, ...) SQL92 coalesce_ [a, b, c, ...] a, b, and c must be of
type Maybe a.
The result has type a
a BETWEEN b AND c SQL92 between_ a b c
a LIKE b SQL92 a `like_` b a and b should be string types
a SIMILAR TO b SQL99 a `similarTo_` b See note for LIKE
POSITION(x IN y) SQL92 position_ x y x and y should be string types
CHAR_LENGTH(x) SQL92 charLength_ x
OCTET_LENGTH(x) SQL92 octetLength_ x
BIT_LENGTH(x) SQL92 bitLength_ x x must be of the beam-specific SqlBitString type
x IS TRUE / x IS NOT TRUE SQL92 isTrue_ x / isNotTrue_ x
x IS FALSE / x IS NOT FALSE SQL92 isFalse_ x / isNotFalse_ x
x IS UNKNOWN / x IS NOT UNKNOWN SQL92 isUnknown_ x / isNotUnknown_ x
NOT x SQL92 not_ x
LOWER (x) SQL92 lower_ x
UPPER (x) SQL92 upper_ x
TRIM (x) SQL92 trim_ x

My favorite operator / function isn't listed here!

If your favorite operator or function is not provided here, first ask yourself if it is part of any SQL standard. If it is not, then check the backend you are using to see if it provides a corresponding construct. If the backend does not or if the function / operator you need is part of a SQL standard, please open an issue on GitHub. Alternatively, implement the construct yourself and send us a pull request! See the section on adding your own functions