| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Database.Esqueleto.Experimental
Synopsis
- data SqlSetOperation a- = Union (SqlSetOperation a) (SqlSetOperation a)
- | UnionAll (SqlSetOperation a) (SqlSetOperation a)
- | Except (SqlSetOperation a) (SqlSetOperation a)
- | Intersect (SqlSetOperation a) (SqlSetOperation a)
- | SelectQuery (SqlQuery a)
 
- data From a where- Table :: PersistEntity ent => From (SqlExpr (Entity ent))
- SubQuery :: (SqlSelect a' r, SqlSelect a'' r', ToAlias a, a' ~ ToAliasT a, ToAliasReference a', ToAliasReferenceT a' ~ a'') => SqlQuery a -> From a''
- SqlSetOperation :: (SqlSelect a' r, ToAlias a, a' ~ ToAliasT a, ToAliasReference a', ToAliasReferenceT a' ~ a'') => SqlSetOperation a -> From a''
- InnerJoinFrom :: From a -> (From b, (a :& b) -> SqlExpr (Value Bool)) -> From (a :& b)
- CrossJoinFrom :: From a -> From b -> From (a :& b)
- LeftJoinFrom :: ToMaybe b => From a -> (From b, (a :& ToMaybeT b) -> SqlExpr (Value Bool)) -> From (a :& ToMaybeT b)
- RightJoinFrom :: ToMaybe a => From a -> (From b, (ToMaybeT a :& b) -> SqlExpr (Value Bool)) -> From (ToMaybeT a :& b)
- FullJoinFrom :: (ToMaybe a, ToMaybe b) => From a -> (From b, (ToMaybeT a :& ToMaybeT b) -> SqlExpr (Value Bool)) -> From (ToMaybeT a :& ToMaybeT b)
 
- on :: ToFrom a => a -> (b -> SqlExpr (Value Bool)) -> (a, b -> SqlExpr (Value Bool))
- from :: ToFrom a => a -> SqlQuery (ToFromT a)
- data a :& b = a :& b
- class ToFrom a where
- type family ToFromT a where ...
- class ToMaybe a where
- type family ToMaybeT a where ...
- class ToAlias a where
- type family ToAliasT a where ...
- class ToAliasReference a where- toAliasReference :: Ident -> a -> SqlQuery (ToAliasReferenceT a)
 
- type family ToAliasReferenceT a where ...
Setup
If you're already using Database.Esqueleto, then you can get started using this module just by changing your imports slightly, as well as enabling the TypeApplications extension.
{-# LANGUAGE TypeApplications #-}
...
import Database.Esqueleto hiding (on, from)
import Database.Esqueleto.Experimental
Introduction
This module is fully backwards-compatible extension to the esqueleto
 EDSL that expands subquery functionality and enables
 SQL set operations
 to be written directly in Haskell. Specifically, this enables:
- Subqueries in JOINstatements
- UNION
- UNION- ALL
- INTERSECT
- EXCEPT
As a consequence of this, several classes of runtime errors are now
 caught at compile time. This includes missing on clauses and improper
 handling of Maybe values in outer joins.
This module can be used in conjunction with the main Database.Esqueleto
 module, but doing so requires qualified imports to avoid ambiguous
 definitions of on and from, which are defined in both modules.
Below we will give an overview of how to use this module and the features it enables.
A New Syntax
This module introduces a new syntax that serves to enable the aforementioned
 features. This new syntax also changes how joins written in the esqueleto
 EDSL to more closely resemble the underlying SQL.
For our examples, we'll use a schema similar to the one in the Getting Started section of Database.Esqueleto:
share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persist|
  Person
    name String
    age Int Maybe
    deriving Eq Show
  BlogPost
    title String
    authorId PersonId
    deriving Eq Show
  Follow
    follower PersonId
    followed PersonId
    deriving Eq Show
|]
Example 1: Simple select
Let's select all people who are named "John".
Database.Esqueleto:
select $ from $ \people -> do where_ (people ^. PersonName ==. val "John") pure people
Database.Esqueleto.Experimental:
select $ do people <- from $ Table @Person where_ (people ^. PersonName ==. val "John") pure people
Example 2: Select with join
Let's select all people and their blog posts who are over the age of 18.
Database.Esqueleto:
select $ from $ \(people `LeftOuterJoin` blogPosts) -> do on (people ^. PersonId ==. blogPosts ?. BlogPostAuthorId) where_ (people ^. PersonAge >. val 18) pure (people, blogPosts)
Database.Esqueleto.Experimental:
Here we use the :& operator to pattern match against the joined tables.
select $ do
(people :& blogPosts) <-
    from $ Table @Person
    `LeftOuterJoin` Table @BlogPost
    `on` (\(people :& blogPosts) ->
            people ^. PersonId ==. blogPosts ?. BlogPostAuthorId)
where_ (people ^. PersonAge >. val 18)
pure (people, blogPosts)
Example 3: Select with multi-table join
Let's select all people who follow a person named "John", including the name of each follower.
Database.Esqueleto:
select $ from $ \( people1 `InnerJoin` followers `InnerJoin` people2 ) -> do on (people1 ^. PersonId ==. followers ^. FollowFollowed) on (followers ^. FollowFollower ==. people2 ^. PersonId) where_ (people1 ^. PersonName ==. val "John") pure (followers, people2)
Database.Esqueleto.Experimental:
In this version, with each successive on clause, only the tables
 we have already joined into are in scope, so we must pattern match
 accordingly. In this case, in the second InnerJoin, we do not use
 the first Person reference, so we use _ as a placeholder to
 ignore it. This prevents a possible runtime error where a table
 is referenced before it appears in the sequence of JOINs.
select $ do
(people1 :& followers :& people2) <-
    from $ Table @Person
    `InnerJoin` Table @Follow
    `on` (\(people1 :& followers) ->
            people1 ^. PersonId ==. followers ^. FollowFollowed)
    `InnerJoin` Table @Person
    `on` (\(_ :& followers :& people2) ->
            followers ^. FollowFollower ==. people2 ^. PersonId)
where_ (people1 ^. PersonName ==. val "John")
pure (followers, people2)
Example 4: Counting results of a subquery
Let's count the number of people who have posted at least 10 posts
Database.Esqueleto:
select $ pure $ subSelectCount $ from $ \( people `InnerJoin` blogPosts ) -> do on (people ^. PersonId ==. blogPosts ^. BlogPostAuthorId) groupBy (people ^. PersonId) having ((count $ blogPosts ^. BlogPostId) >. val 10) pure people
Database.Esqueleto.Experimental:
select $ do
peopleWithPosts <-
  from $ SelectQuery $ do
    (people :& blogPosts) <-
      from $ Table @Person
      `InnerJoin` Table @BlogPost
      `on` (\(p :& bP) ->
              p ^. PersonId ==. bP ^. BlogPostAuthorId)
    groupBy (people ^. PersonId)
    having ((count $ blogPosts ^. BlogPostId) >. val 10)
    pure people
pure $ count (peopleWithPosts ^. PersonId)
We now have the ability to refactor this
Example 5: Sorting the results of a UNION with limits
Out of all of the posts created by a person and the people they follow, generate a list of the first 25 posts, sorted alphabetically.
Database.Esqueleto:
Since UNION is not supported, this requires using rawSql. (Not shown)
Database.Esqueleto.Experimental:
Since this module supports all set operations (see SqlSetOperation), we can use
 Union to write this query.
select $ do
(authors, blogPosts) <- from $
  (SelectQuery $ do
    (author :& blogPost) <-
      from $ Table @Person
      `InnerJoin` Table @BlogPost
      `on` (\(a :& bP) ->
              a ^. PersonId ==. bP ^. BlogPostAuthorId)
    where_ (author ^. PersonId ==. val currentPersonId)
    pure (author, blogPost)
  )
  `Union`
  (SelectQuery $ do
    (follow :& blogPost :& author) <-
      from $ Table @Follow
      `InnerJoin` Table @BlogPost
      `on` (\(f :& bP) ->
              f ^. FollowFollowed ==. bP ^. BlogPostAuthorId)
      `InnerJoin` Table @Person
      `on` (\(_ :& bP :& a) ->
              bP ^. BlogPostAuthorId ==. a ^. PersonId)
    where_ (follow ^. FollowFollower ==. val currentPersonId)
    pure (author, blogPost)
  )
orderBy [ asc (blogPosts ^. BlogPostTitle) ]
limit 25
pure (authors, blogPosts)
Documentation
data SqlSetOperation a Source #
Data type that represents SQL set operations. This includes
 UNION, UNION ALL, EXCEPT, and INTERSECT. This data
 type is defined as a binary tree, with SelectQuery on the leaves.
Each constructor corresponding to the aforementioned set operations
 can be used as an infix function in a from to help with readability
 and lead to code that closely resembles the underlying SQL. For example,
select $ from $ (SelectQuery ...) `Union` (SelectQuery ...)
is translated into
SELECT * FROM ( (SELECT * FROM ...) UNION (SELECT * FROM ...) )
SelectQuery can be used without any of the set operations to construct
 a subquery. This can be used in JOIN trees. For example,
select $ from $ Table @SomeTable `InnerJoin` (SelectQuery ...) `on` ...
is translated into
SELECT * FROM SomeTable INNER JOIN (SELECT * FROM ...) ON ...
Constructors
| Union (SqlSetOperation a) (SqlSetOperation a) | |
| UnionAll (SqlSetOperation a) (SqlSetOperation a) | |
| Except (SqlSetOperation a) (SqlSetOperation a) | |
| Intersect (SqlSetOperation a) (SqlSetOperation a) | |
| SelectQuery (SqlQuery a) | 
Instances
| (SqlSelect a' r, SqlSelect a'' r', ToAlias a, a' ~ ToAliasT a, ToAliasReference a', ToAliasReferenceT a' ~ a'') => ToFrom (SqlSetOperation a) Source # | |
| Defined in Database.Esqueleto.Experimental Methods toFrom :: SqlSetOperation a -> From (ToFromT (SqlSetOperation a)) Source # | |
Data type that represents the syntax of a JOIN tree. In practice,
 only the Table constructor is used directly when writing queries. For example,
select $ from $ Table @People
Constructors
| Table :: PersistEntity ent => From (SqlExpr (Entity ent)) | |
| SubQuery :: (SqlSelect a' r, SqlSelect a'' r', ToAlias a, a' ~ ToAliasT a, ToAliasReference a', ToAliasReferenceT a' ~ a'') => SqlQuery a -> From a'' | |
| SqlSetOperation :: (SqlSelect a' r, ToAlias a, a' ~ ToAliasT a, ToAliasReference a', ToAliasReferenceT a' ~ a'') => SqlSetOperation a -> From a'' | |
| InnerJoinFrom :: From a -> (From b, (a :& b) -> SqlExpr (Value Bool)) -> From (a :& b) | |
| CrossJoinFrom :: From a -> From b -> From (a :& b) | |
| LeftJoinFrom :: ToMaybe b => From a -> (From b, (a :& ToMaybeT b) -> SqlExpr (Value Bool)) -> From (a :& ToMaybeT b) | |
| RightJoinFrom :: ToMaybe a => From a -> (From b, (ToMaybeT a :& b) -> SqlExpr (Value Bool)) -> From (ToMaybeT a :& b) | |
| FullJoinFrom :: (ToMaybe a, ToMaybe b) => From a -> (From b, (ToMaybeT a :& ToMaybeT b) -> SqlExpr (Value Bool)) -> From (ToMaybeT a :& ToMaybeT b) | 
on :: ToFrom a => a -> (b -> SqlExpr (Value Bool)) -> (a, b -> SqlExpr (Value Bool)) infix 9 Source #
An ON clause that describes how two tables are related. This should be
 used as an infix operator after a JOIN. For example,
select $
from $ Table @Person
`InnerJoin` Table @BlogPost
`on` (\(p :& bP) ->
        p ^. PersonId ==. bP ^. BlogPostAuthorId)
from :: ToFrom a => a -> SqlQuery (ToFromT a) Source #
FROM clause, used to bring entities into scope.
Internally, this function uses the From datatype and the
 ToFrom typeclass. Unlike the old from,
 this does not take a function as a parameter, but rather
 a value that represents a JOIN tree constructed out of
 instances of ToFrom. This implementation eliminates certain
 types of runtime errors by preventing the construction of
 invalid SQL (e.g. illegal nested-from).
A left-precedence pair. Pronounced "and". Used to represent expressions that have been joined together.
The precedence behavior can be demonstrated by:
a :& b :& c == ((a :& b) :& c)
See the examples at the beginning of this module to see how this
 operator is used in JOIN operations.
Constructors
| a :& b infixl 2 | 
Instances
| (ToMaybe a, ToMaybe b) => ToMaybe (a :& b) Source # | |
| (ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b', ToMaybe a', ma ~ ToMaybeT a', ToMaybe b', mb ~ ToMaybeT b') => ToFrom (FullOuterJoin a (b, (ma :& mb) -> SqlExpr (Value Bool))) Source # | |
| (ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b', ToMaybe a', ma ~ ToMaybeT a') => ToFrom (RightOuterJoin a (b, (ma :& b') -> SqlExpr (Value Bool))) Source # | |
| (ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b', ToMaybe b', mb ~ ToMaybeT b') => ToFrom (LeftOuterJoin a (b, (a' :& mb) -> SqlExpr (Value Bool))) Source # | |
| (ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b') => ToFrom (InnerJoin a (b, (a' :& b') -> SqlExpr (Value Bool))) Source # | |
Internals
Instances
type family ToFromT a where ... Source #
Equations
| ToFromT (From a) = a | |
| ToFromT (SqlSetOperation a) = ToAliasReferenceT (ToAliasT a) | |
| ToFromT (LeftOuterJoin a (b, c -> SqlExpr (Value Bool))) = c | |
| ToFromT (FullOuterJoin a (b, c -> SqlExpr (Value Bool))) = c | |
| ToFromT (RightOuterJoin a (b, c -> SqlExpr (Value Bool))) = c | |
| ToFromT (InnerJoin a (b, c -> SqlExpr (Value Bool))) = c | |
| ToFromT (CrossJoin a b) = ToFromT a :& ToFromT b | |
| ToFromT (InnerJoin a b) = TypeError (JoinErrorMsg "InnerJoin") | |
| ToFromT (LeftOuterJoin a b) = TypeError (JoinErrorMsg "LeftOuterJoin") | |
| ToFromT (RightOuterJoin a b) = TypeError (JoinErrorMsg "RightOuterJoin") | |
| ToFromT (FullOuterJoin a b) = TypeError (JoinErrorMsg "FullOuterJoin") | 
class ToMaybe a where Source #
Instances
type family ToMaybeT a where ... Source #
Equations
| ToMaybeT (SqlExpr (Maybe a)) = SqlExpr (Maybe a) | |
| ToMaybeT (SqlExpr (Entity a)) = SqlExpr (Maybe (Entity a)) | |
| ToMaybeT (SqlExpr (Value a)) = SqlExpr (Value (Maybe (Nullable a))) | |
| ToMaybeT (a :& b) = ToMaybeT a :& ToMaybeT b | |
| ToMaybeT (a, b) = (ToMaybeT a, ToMaybeT b) | |
| ToMaybeT (a, b, c) = (ToMaybeT a, ToMaybeT b, ToMaybeT c) | |
| ToMaybeT (a, b, c, d) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d) | |
| ToMaybeT (a, b, c, d, e) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e) | |
| ToMaybeT (a, b, c, d, e, f) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e, ToMaybeT f) | |
| ToMaybeT (a, b, c, d, e, f, g) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e, ToMaybeT f, ToMaybeT g) | |
| ToMaybeT (a, b, c, d, e, f, g, h) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e, ToMaybeT f, ToMaybeT g, ToMaybeT h) | 
class ToAlias a where Source #
Instances
| ToAlias (SqlExpr (Entity a)) Source # | |
| ToAlias (SqlExpr (Value a)) Source # | |
| (ToAlias a, ToAlias b) => ToAlias (a, b) Source # | |
| (ToAlias a, ToAlias b, ToAlias c) => ToAlias (a, b, c) Source # | |
| (ToAlias a, ToAlias b, ToAlias c, ToAlias d) => ToAlias (a, b, c, d) Source # | |
| (ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e) => ToAlias (a, b, c, d, e) Source # | |
| (ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e, ToAlias f) => ToAlias (a, b, c, d, e, f) Source # | |
| (ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e, ToAlias f, ToAlias g) => ToAlias (a, b, c, d, e, f, g) Source # | |
| (ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e, ToAlias f, ToAlias g, ToAlias h) => ToAlias (a, b, c, d, e, f, g, h) Source # | |
type family ToAliasT a where ... Source #
Equations
| ToAliasT (SqlExpr (Value a)) = SqlExpr (Value a) | |
| ToAliasT (SqlExpr (Entity a)) = SqlExpr (Entity a) | |
| ToAliasT (a, b) = (ToAliasT a, ToAliasT b) | |
| ToAliasT (a, b, c) = (ToAliasT a, ToAliasT b, ToAliasT c) | |
| ToAliasT (a, b, c, d) = (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d) | |
| ToAliasT (a, b, c, d, e) = (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e) | |
| ToAliasT (a, b, c, d, e, f) = (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e, ToAliasT f) | |
| ToAliasT (a, b, c, d, e, f, g) = (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e, ToAliasT f, ToAliasT g) | |
| ToAliasT (a, b, c, d, e, f, g, h) = (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e, ToAliasT f, ToAliasT g, ToAliasT h) | 
class ToAliasReference a where Source #
Methods
toAliasReference :: Ident -> a -> SqlQuery (ToAliasReferenceT a) Source #
Instances
type family ToAliasReferenceT a where ... Source #
Equations