{-# LANGUAGE CPP
           , DataKinds
           , FlexibleContexts
           , FlexibleInstances
           , FunctionalDependencies
           , GADTs
           , MultiParamTypeClasses
           , TypeOperators
           , TypeFamilies
           , UndecidableInstances
           , OverloadedStrings
           , PatternSynonyms
 #-}

-- | This module contains a new way (introduced in 3.3.3.0) of using @FROM@ in
-- Haskell. The old method was a bit finicky and could permit runtime errors,
-- and this new way is both significantly safer and much more powerful.
--
-- Esqueleto users are encouraged to migrate to this module, as it will become
-- the default in a new major version @4.0.0.0@.
module Database.Esqueleto.Experimental
    ( -- * Setup
      -- $setup

      -- * Introduction
      -- $introduction

      -- * A New Syntax
      -- $new-syntax

      -- * Documentation

      SqlSetOperation(Union, UnionAll, Except, Intersect)
    , pattern SelectQuery
    , From(..)
    , on
    , from
    , (:&)(..)
      -- * Internals
    , ToFrom(..)
    , ToFromT
    , ToMaybe(..)
    , ToMaybeT
    , ToAlias(..)
    , ToAliasT
    , ToAliasReference(..)
    , ToAliasReferenceT
    -- * The Normal Stuff
    , module Database.Esqueleto
    )
    where

import Database.Esqueleto hiding (from, on, From(..))
import qualified Control.Monad.Trans.Writer as W
import qualified Control.Monad.Trans.State as S
import Control.Monad.Trans.Class (lift)
#if __GLASGOW_HASKELL__ < 804
import Data.Semigroup
#endif
import Data.Proxy (Proxy(..))
import Database.Esqueleto.Internal.PersistentImport
import Database.Esqueleto.Internal.Internal
          ( SqlExpr(..)
          , InnerJoin(..)
          , CrossJoin(..)
          , LeftOuterJoin(..)
          , RightOuterJoin(..)
          , FullOuterJoin(..)
          , FromClause(..)
          , SqlQuery(..)
          , SideData(..)
          , Value(..)
          , JoinKind(..)
          , newIdentFor
          , SqlSelect(..)
          , Mode(..)
          , toRawSql
          , Ident(..)
          , to3, to4, to5, to6, to7, to8
          , from3, from4, from5, from6, from7, from8
          , veryUnsafeCoerceSqlExprValue
          , parensM
          , NeedParens(..)
          )
import GHC.TypeLits

-- $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](https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html#extension-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](https://en.wikipedia.org/wiki/Set_operations_(SQL\))
-- to be written directly in Haskell. Specifically, this enables:
--
--   * Subqueries in 'JOIN' statements
--   * '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.

----------------------------------------------------------------------

-- $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 'JOIN's.
--
-- @
-- 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 `Database.Esqueleto.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)
-- @

-- | 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.
data (:&) a b = a :& b
infixl 2 :&

-- | 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 ...
-- @
data SqlSetOperation a =
    Union (SqlSetOperation a) (SqlSetOperation a)
  | UnionAll (SqlSetOperation a) (SqlSetOperation a)
  | Except (SqlSetOperation a) (SqlSetOperation a)
  | Intersect (SqlSetOperation a) (SqlSetOperation a)
  | SelectQueryP NeedParens (SqlQuery a)

pattern SelectQuery :: SqlQuery a -> SqlSetOperation a
pattern $bSelectQuery :: SqlQuery a -> SqlSetOperation a
$mSelectQuery :: forall r a.
SqlSetOperation a -> (SqlQuery a -> r) -> (Void# -> r) -> r
SelectQuery q = SelectQueryP Never q

-- | 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
-- @
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)

-- | 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)
-- @
--
on :: ToFrom a => a -> (b -> SqlExpr (Value Bool)) -> (a, b -> SqlExpr (Value Bool))
on :: a -> (b -> SqlExpr (Value Bool)) -> (a, b -> SqlExpr (Value Bool))
on = (,)
infix 9 `on`

type JoinErrorMsg jk = 'Text "Missing on statement for " ':<>: 'Text jk

type family ToFromT a where
  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")

{-- Type class magic to allow the use of the `InnerJoin` family of data constructors in from --}
class ToFrom a where
  toFrom :: a -> From (ToFromT a)

instance ToFrom (From a) where
  toFrom :: From a -> From (ToFromT (From a))
toFrom = From a -> From (ToFromT (From a))
forall a. a -> a
id

instance {-# OVERLAPPABLE #-} ToFrom (InnerJoin a b) where
  toFrom :: InnerJoin a b -> From (ToFromT (InnerJoin a b))
toFrom = InnerJoin a b -> From (ToFromT (InnerJoin a b))
forall a. HasCallStack => a
undefined
instance {-# OVERLAPPABLE #-} ToFrom (LeftOuterJoin a b) where
  toFrom :: LeftOuterJoin a b -> From (ToFromT (LeftOuterJoin a b))
toFrom = LeftOuterJoin a b -> From (ToFromT (LeftOuterJoin a b))
forall a. HasCallStack => a
undefined
instance {-# OVERLAPPABLE #-} ToFrom (RightOuterJoin a b) where
  toFrom :: RightOuterJoin a b -> From (ToFromT (RightOuterJoin a b))
toFrom = RightOuterJoin a b -> From (ToFromT (RightOuterJoin a b))
forall a. HasCallStack => a
undefined
instance {-# OVERLAPPABLE #-} ToFrom (FullOuterJoin a b) where
  toFrom :: FullOuterJoin a b -> From (ToFromT (FullOuterJoin a b))
toFrom = FullOuterJoin a b -> From (ToFromT (FullOuterJoin a b))
forall a. HasCallStack => a
undefined

instance (SqlSelect a' r,SqlSelect a'' r', ToAlias a, a' ~ ToAliasT a, ToAliasReference a', ToAliasReferenceT a' ~ a'')  => ToFrom (SqlSetOperation a) where
  -- If someone uses just a plain SelectQuery it should behave like a normal subquery
  toFrom :: SqlSetOperation a -> From (ToFromT (SqlSetOperation a))
toFrom (SelectQueryP NeedParens
_ SqlQuery a
q) = SqlQuery a -> From a''
forall a' r a'' a' r.
(SqlSelect a' r, SqlSelect a'' a', ToAlias r, a' ~ ToAliasT r,
 ToAliasReference a', ToAliasReferenceT a' ~ a'') =>
SqlQuery r -> From a''
SubQuery SqlQuery a
q
  -- Otherwise use the SqlSetOperation
  toFrom SqlSetOperation a
q = SqlSetOperation a -> From a''
forall a' r a a''.
(SqlSelect a' r, ToAlias a, a' ~ ToAliasT a, ToAliasReference a',
 ToAliasReferenceT a' ~ a'') =>
SqlSetOperation a -> From a''
SqlSetOperation SqlSetOperation a
q

instance (ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b', ToMaybe b', mb ~ ToMaybeT b')
       => ToFrom (LeftOuterJoin a (b, (a' :& mb) -> SqlExpr (Value Bool))) where
  toFrom :: LeftOuterJoin a (b, (a' :& mb) -> SqlExpr (Value Bool))
-> From
     (ToFromT (LeftOuterJoin a (b, (a' :& mb) -> SqlExpr (Value Bool))))
toFrom (LeftOuterJoin a
lhs (b
rhs, (a' :& mb) -> SqlExpr (Value Bool)
on')) = From a'
-> (From b', (a' :& ToMaybeT b') -> SqlExpr (Value Bool))
-> From (a' :& ToMaybeT b')
forall b a.
ToMaybe b =>
From a
-> (From b, (a :& ToMaybeT b) -> SqlExpr (Value Bool))
-> From (a :& ToMaybeT b)
LeftJoinFrom (a -> From (ToFromT a)
forall a. ToFrom a => a -> From (ToFromT a)
toFrom a
lhs) (b -> From (ToFromT b)
forall a. ToFrom a => a -> From (ToFromT a)
toFrom b
rhs, (a' :& mb) -> SqlExpr (Value Bool)
(a' :& ToMaybeT b') -> SqlExpr (Value Bool)
on')

instance (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))) where
  toFrom :: FullOuterJoin a (b, (ma :& mb) -> SqlExpr (Value Bool))
-> From
     (ToFromT (FullOuterJoin a (b, (ma :& mb) -> SqlExpr (Value Bool))))
toFrom (FullOuterJoin a
lhs (b
rhs, (ma :& mb) -> SqlExpr (Value Bool)
on')) = From a'
-> (From b', (ToMaybeT a' :& ToMaybeT b') -> SqlExpr (Value Bool))
-> From (ToMaybeT a' :& ToMaybeT b')
forall b b.
(ToMaybe b, ToMaybe b) =>
From b
-> (From b, (ToMaybeT b :& ToMaybeT b) -> SqlExpr (Value Bool))
-> From (ToMaybeT b :& ToMaybeT b)
FullJoinFrom (a -> From (ToFromT a)
forall a. ToFrom a => a -> From (ToFromT a)
toFrom a
lhs) (b -> From (ToFromT b)
forall a. ToFrom a => a -> From (ToFromT a)
toFrom b
rhs, (ma :& mb) -> SqlExpr (Value Bool)
(ToMaybeT a' :& ToMaybeT b') -> SqlExpr (Value Bool)
on')

instance (ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b', ToMaybe a', ma ~ ToMaybeT a')
       => ToFrom (RightOuterJoin a (b, (ma :& b') -> SqlExpr (Value Bool))) where
  toFrom :: RightOuterJoin a (b, (ma :& b') -> SqlExpr (Value Bool))
-> From
     (ToFromT
        (RightOuterJoin a (b, (ma :& b') -> SqlExpr (Value Bool))))
toFrom (RightOuterJoin a
lhs (b
rhs, (ma :& b') -> SqlExpr (Value Bool)
on')) = From a'
-> (From b', (ToMaybeT a' :& b') -> SqlExpr (Value Bool))
-> From (ToMaybeT a' :& b')
forall a b.
ToMaybe a =>
From a
-> (From b, (ToMaybeT a :& b) -> SqlExpr (Value Bool))
-> From (ToMaybeT a :& b)
RightJoinFrom (a -> From (ToFromT a)
forall a. ToFrom a => a -> From (ToFromT a)
toFrom a
lhs) (b -> From (ToFromT b)
forall a. ToFrom a => a -> From (ToFromT a)
toFrom b
rhs, (ma :& b') -> SqlExpr (Value Bool)
(ToMaybeT a' :& b') -> SqlExpr (Value Bool)
on')

instance (ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b') => ToFrom (InnerJoin a (b, (a' :& b') -> SqlExpr (Value Bool))) where
  toFrom :: InnerJoin a (b, (a' :& b') -> SqlExpr (Value Bool))
-> From
     (ToFromT (InnerJoin a (b, (a' :& b') -> SqlExpr (Value Bool))))
toFrom (InnerJoin a
lhs (b
rhs, (a' :& b') -> SqlExpr (Value Bool)
on')) = From a'
-> (From b', (a' :& b') -> SqlExpr (Value Bool)) -> From (a' :& b')
forall a a.
From a
-> (From a, (a :& a) -> SqlExpr (Value Bool)) -> From (a :& a)
InnerJoinFrom (a -> From (ToFromT a)
forall a. ToFrom a => a -> From (ToFromT a)
toFrom a
lhs) (b -> From (ToFromT b)
forall a. ToFrom a => a -> From (ToFromT a)
toFrom b
rhs, (a' :& b') -> SqlExpr (Value Bool)
on')

instance (ToFrom a, ToFrom b) => ToFrom (CrossJoin a b) where
  toFrom :: CrossJoin a b -> From (ToFromT (CrossJoin a b))
toFrom (CrossJoin a
lhs b
rhs) = From (ToFromT a)
-> From (ToFromT b) -> From (ToFromT a :& ToFromT b)
forall a b. From a -> From b -> From (a :& b)
CrossJoinFrom (a -> From (ToFromT a)
forall a. ToFrom a => a -> From (ToFromT a)
toFrom a
lhs) (b -> From (ToFromT b)
forall a. ToFrom a => a -> From (ToFromT a)
toFrom b
rhs)

type family Nullable a where
  Nullable (Maybe a) = a
  Nullable a =  a

type family ToMaybeT a where
  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 ToMaybe a where
  toMaybe :: a -> ToMaybeT a

instance ToMaybe (SqlExpr (Maybe a)) where
  toMaybe :: SqlExpr (Maybe a) -> ToMaybeT (SqlExpr (Maybe a))
toMaybe = SqlExpr (Maybe a) -> ToMaybeT (SqlExpr (Maybe a))
forall a. a -> a
id

instance ToMaybe (SqlExpr (Entity a)) where
  toMaybe :: SqlExpr (Entity a) -> ToMaybeT (SqlExpr (Entity a))
toMaybe = SqlExpr (Entity a) -> ToMaybeT (SqlExpr (Entity a))
forall a. SqlExpr a -> SqlExpr (Maybe a)
EMaybe

instance ToMaybe (SqlExpr (Value a)) where
  toMaybe :: SqlExpr (Value a) -> ToMaybeT (SqlExpr (Value a))
toMaybe = SqlExpr (Value a) -> ToMaybeT (SqlExpr (Value a))
forall a b. SqlExpr (Value a) -> SqlExpr (Value b)
veryUnsafeCoerceSqlExprValue

instance (ToMaybe a, ToMaybe b) => ToMaybe (a :& b) where
  toMaybe :: (a :& b) -> ToMaybeT (a :& b)
toMaybe (a
a :& b
b) = (a -> ToMaybeT a
forall a. ToMaybe a => a -> ToMaybeT a
toMaybe a
a ToMaybeT a -> ToMaybeT b -> ToMaybeT a :& ToMaybeT b
forall a b. a -> b -> a :& b
:& b -> ToMaybeT b
forall a. ToMaybe a => a -> ToMaybeT a
toMaybe b
b)

instance (ToMaybe a, ToMaybe b) => ToMaybe (a,b) where
  toMaybe :: (a, b) -> ToMaybeT (a, b)
toMaybe (a
a, b
b) = (a -> ToMaybeT a
forall a. ToMaybe a => a -> ToMaybeT a
toMaybe a
a, b -> ToMaybeT b
forall a. ToMaybe a => a -> ToMaybeT a
toMaybe b
b)

instance ( ToMaybe a
         , ToMaybe b
         , ToMaybe c
         ) => ToMaybe (a,b,c) where
  toMaybe :: (a, b, c) -> ToMaybeT (a, b, c)
toMaybe = ((ToMaybeT a, ToMaybeT b), ToMaybeT c)
-> (ToMaybeT a, ToMaybeT b, ToMaybeT c)
forall a b c. ((a, b), c) -> (a, b, c)
to3 (((ToMaybeT a, ToMaybeT b), ToMaybeT c)
 -> (ToMaybeT a, ToMaybeT b, ToMaybeT c))
-> ((a, b, c) -> ((ToMaybeT a, ToMaybeT b), ToMaybeT c))
-> (a, b, c)
-> (ToMaybeT a, ToMaybeT b, ToMaybeT c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, b), c) -> ((ToMaybeT a, ToMaybeT b), ToMaybeT c)
forall a. ToMaybe a => a -> ToMaybeT a
toMaybe (((a, b), c) -> ((ToMaybeT a, ToMaybeT b), ToMaybeT c))
-> ((a, b, c) -> ((a, b), c))
-> (a, b, c)
-> ((ToMaybeT a, ToMaybeT b), ToMaybeT c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b, c) -> ((a, b), c)
forall a b c. (a, b, c) -> ((a, b), c)
from3

instance ( ToMaybe a
         , ToMaybe b
         , ToMaybe c
         , ToMaybe d
         ) => ToMaybe (a,b,c,d) where
  toMaybe :: (a, b, c, d) -> ToMaybeT (a, b, c, d)
toMaybe = ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d))
-> (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d)
forall a b c d. ((a, b), (c, d)) -> (a, b, c, d)
to4 (((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d))
 -> (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d))
-> ((a, b, c, d)
    -> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d)))
-> (a, b, c, d)
-> (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, b), (c, d))
-> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d))
forall a. ToMaybe a => a -> ToMaybeT a
toMaybe (((a, b), (c, d))
 -> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d)))
-> ((a, b, c, d) -> ((a, b), (c, d)))
-> (a, b, c, d)
-> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b, c, d) -> ((a, b), (c, d))
forall a b c d. (a, b, c, d) -> ((a, b), (c, d))
from4

instance ( ToMaybe a
         , ToMaybe b
         , ToMaybe c
         , ToMaybe d
         , ToMaybe e
         ) => ToMaybe (a,b,c,d,e) where
  toMaybe :: (a, b, c, d, e) -> ToMaybeT (a, b, c, d, e)
toMaybe = ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d), ToMaybeT e)
-> (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e)
forall a b c d e. ((a, b), (c, d), e) -> (a, b, c, d, e)
to5 (((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d), ToMaybeT e)
 -> (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e))
-> ((a, b, c, d, e)
    -> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
        ToMaybeT e))
-> (a, b, c, d, e)
-> (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, b), (c, d), e)
-> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d), ToMaybeT e)
forall a. ToMaybe a => a -> ToMaybeT a
toMaybe (((a, b), (c, d), e)
 -> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
     ToMaybeT e))
-> ((a, b, c, d, e) -> ((a, b), (c, d), e))
-> (a, b, c, d, e)
-> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d), ToMaybeT e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b, c, d, e) -> ((a, b), (c, d), e)
forall a b c d e. (a, b, c, d, e) -> ((a, b), (c, d), e)
from5

instance ( ToMaybe a
         , ToMaybe b
         , ToMaybe c
         , ToMaybe d
         , ToMaybe e
         , ToMaybe f
         ) => ToMaybe (a,b,c,d,e,f) where
  toMaybe :: (a, b, c, d, e, f) -> ToMaybeT (a, b, c, d, e, f)
toMaybe = ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
 (ToMaybeT e, ToMaybeT f))
-> (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e,
    ToMaybeT f)
forall a b c d e f. ((a, b), (c, d), (e, f)) -> (a, b, c, d, e, f)
to6 (((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
  (ToMaybeT e, ToMaybeT f))
 -> (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e,
     ToMaybeT f))
-> ((a, b, c, d, e, f)
    -> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
        (ToMaybeT e, ToMaybeT f)))
-> (a, b, c, d, e, f)
-> (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e,
    ToMaybeT f)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, b), (c, d), (e, f))
-> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
    (ToMaybeT e, ToMaybeT f))
forall a. ToMaybe a => a -> ToMaybeT a
toMaybe (((a, b), (c, d), (e, f))
 -> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
     (ToMaybeT e, ToMaybeT f)))
-> ((a, b, c, d, e, f) -> ((a, b), (c, d), (e, f)))
-> (a, b, c, d, e, f)
-> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
    (ToMaybeT e, ToMaybeT f))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b, c, d, e, f) -> ((a, b), (c, d), (e, f))
forall a b c d e f. (a, b, c, d, e, f) -> ((a, b), (c, d), (e, f))
from6

instance ( ToMaybe a
         , ToMaybe b
         , ToMaybe c
         , ToMaybe d
         , ToMaybe e
         , ToMaybe f
         , ToMaybe g
         ) => ToMaybe (a,b,c,d,e,f,g) where
  toMaybe :: (a, b, c, d, e, f, g) -> ToMaybeT (a, b, c, d, e, f, g)
toMaybe = ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
 (ToMaybeT e, ToMaybeT f), ToMaybeT g)
-> (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e,
    ToMaybeT f, ToMaybeT g)
forall a b c d e f g.
((a, b), (c, d), (e, f), g) -> (a, b, c, d, e, f, g)
to7 (((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
  (ToMaybeT e, ToMaybeT f), ToMaybeT g)
 -> (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e,
     ToMaybeT f, ToMaybeT g))
-> ((a, b, c, d, e, f, g)
    -> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
        (ToMaybeT e, ToMaybeT f), ToMaybeT g))
-> (a, b, c, d, e, f, g)
-> (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e,
    ToMaybeT f, ToMaybeT g)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, b), (c, d), (e, f), g)
-> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
    (ToMaybeT e, ToMaybeT f), ToMaybeT g)
forall a. ToMaybe a => a -> ToMaybeT a
toMaybe (((a, b), (c, d), (e, f), g)
 -> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
     (ToMaybeT e, ToMaybeT f), ToMaybeT g))
-> ((a, b, c, d, e, f, g) -> ((a, b), (c, d), (e, f), g))
-> (a, b, c, d, e, f, g)
-> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
    (ToMaybeT e, ToMaybeT f), ToMaybeT g)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b, c, d, e, f, g) -> ((a, b), (c, d), (e, f), g)
forall a b c d e f g.
(a, b, c, d, e, f, g) -> ((a, b), (c, d), (e, f), g)
from7

instance ( ToMaybe a
         , ToMaybe b
         , ToMaybe c
         , ToMaybe d
         , ToMaybe e
         , ToMaybe f
         , ToMaybe g
         , ToMaybe h
         ) => ToMaybe (a,b,c,d,e,f,g,h) where
  toMaybe :: (a, b, c, d, e, f, g, h) -> ToMaybeT (a, b, c, d, e, f, g, h)
toMaybe = ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
 (ToMaybeT e, ToMaybeT f), (ToMaybeT g, ToMaybeT h))
-> (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e,
    ToMaybeT f, ToMaybeT g, ToMaybeT h)
forall a b c d e f g h.
((a, b), (c, d), (e, f), (g, h)) -> (a, b, c, d, e, f, g, h)
to8 (((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
  (ToMaybeT e, ToMaybeT f), (ToMaybeT g, ToMaybeT h))
 -> (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e,
     ToMaybeT f, ToMaybeT g, ToMaybeT h))
-> ((a, b, c, d, e, f, g, h)
    -> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
        (ToMaybeT e, ToMaybeT f), (ToMaybeT g, ToMaybeT h)))
-> (a, b, c, d, e, f, g, h)
-> (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e,
    ToMaybeT f, ToMaybeT g, ToMaybeT h)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, b), (c, d), (e, f), (g, h))
-> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
    (ToMaybeT e, ToMaybeT f), (ToMaybeT g, ToMaybeT h))
forall a. ToMaybe a => a -> ToMaybeT a
toMaybe (((a, b), (c, d), (e, f), (g, h))
 -> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
     (ToMaybeT e, ToMaybeT f), (ToMaybeT g, ToMaybeT h)))
-> ((a, b, c, d, e, f, g, h) -> ((a, b), (c, d), (e, f), (g, h)))
-> (a, b, c, d, e, f, g, h)
-> ((ToMaybeT a, ToMaybeT b), (ToMaybeT c, ToMaybeT d),
    (ToMaybeT e, ToMaybeT f), (ToMaybeT g, ToMaybeT h))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, b, c, d, e, f, g, h) -> ((a, b), (c, d), (e, f), (g, h))
forall a b c d e f g h.
(a, b, c, d, e, f, g, h) -> ((a, b), (c, d), (e, f), (g, h))
from8

-- | 'FROM' clause, used to bring entities into scope.
--
-- Internally, this function uses the `From` datatype and the
-- `ToFrom` typeclass. Unlike the old `Database.Esqueleto.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@).
from :: ToFrom a  => a -> SqlQuery (ToFromT a)
from :: a -> SqlQuery (ToFromT a)
from a
parts = do
  (ToFromT a
a, FromClause
clause) <- From (ToFromT a) -> SqlQuery (ToFromT a, FromClause)
forall a. From a -> SqlQuery (a, FromClause)
runFrom (From (ToFromT a) -> SqlQuery (ToFromT a, FromClause))
-> From (ToFromT a) -> SqlQuery (ToFromT a, FromClause)
forall a b. (a -> b) -> a -> b
$ a -> From (ToFromT a)
forall a. ToFrom a => a -> From (ToFromT a)
toFrom a
parts
  WriterT SideData (State IdentState) () -> SqlQuery ()
forall a. WriterT SideData (State IdentState) a -> SqlQuery a
Q (WriterT SideData (State IdentState) () -> SqlQuery ())
-> WriterT SideData (State IdentState) () -> SqlQuery ()
forall a b. (a -> b) -> a -> b
$ SideData -> WriterT SideData (State IdentState) ()
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
W.tell SideData
forall a. Monoid a => a
mempty{sdFromClause :: [FromClause]
sdFromClause=[FromClause
clause]}
  ToFromT a -> SqlQuery (ToFromT a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ToFromT a
a
    where
      runFrom :: From a -> SqlQuery (a, FromClause)
      runFrom :: From a -> SqlQuery (a, FromClause)
runFrom e :: From a
e@From a
Table = do
        let ed :: EntityDef
ed = Proxy ent -> EntityDef
forall record (m :: * -> *).
(PersistEntity record, Monad m) =>
m record -> EntityDef
entityDef (Proxy ent -> EntityDef) -> Proxy ent -> EntityDef
forall a b. (a -> b) -> a -> b
$ From (SqlExpr (Entity ent)) -> Proxy ent
forall ent.
PersistEntity ent =>
From (SqlExpr (Entity ent)) -> Proxy ent
getVal From a
From (SqlExpr (Entity ent))
e
        Ident
ident <- DBName -> SqlQuery Ident
newIdentFor (EntityDef -> DBName
entityDB EntityDef
ed)
        let entity :: SqlExpr (Entity ent)
entity = Ident -> SqlExpr (Entity ent)
forall val. Ident -> SqlExpr (Entity val)
EEntity Ident
ident
        (SqlExpr (Entity ent), FromClause)
-> SqlQuery (SqlExpr (Entity ent), FromClause)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((SqlExpr (Entity ent), FromClause)
 -> SqlQuery (SqlExpr (Entity ent), FromClause))
-> (SqlExpr (Entity ent), FromClause)
-> SqlQuery (SqlExpr (Entity ent), FromClause)
forall a b. (a -> b) -> a -> b
$ (SqlExpr (Entity ent)
entity, Ident -> EntityDef -> FromClause
FromStart Ident
ident EntityDef
ed)
          where
            getVal :: PersistEntity ent => From (SqlExpr (Entity ent)) -> Proxy ent
            getVal :: From (SqlExpr (Entity ent)) -> Proxy ent
getVal = Proxy ent -> From (SqlExpr (Entity ent)) -> Proxy ent
forall a b. a -> b -> a
const Proxy ent
forall k (t :: k). Proxy t
Proxy
      runFrom (SubQuery SqlQuery a
subquery) = do
          -- We want to update the IdentState without writing the query to side data
          (a
ret, SideData
sideData) <- WriterT SideData (State IdentState) (a, SideData)
-> SqlQuery (a, SideData)
forall a. WriterT SideData (State IdentState) a -> SqlQuery a
Q (WriterT SideData (State IdentState) (a, SideData)
 -> SqlQuery (a, SideData))
-> WriterT SideData (State IdentState) (a, SideData)
-> SqlQuery (a, SideData)
forall a b. (a -> b) -> a -> b
$ (SideData -> SideData)
-> WriterT SideData (State IdentState) (a, SideData)
-> WriterT SideData (State IdentState) (a, SideData)
forall (m :: * -> *) w a.
Monad m =>
(w -> w) -> WriterT w m a -> WriterT w m a
W.censor (\SideData
_ -> SideData
forall a. Monoid a => a
mempty) (WriterT SideData (State IdentState) (a, SideData)
 -> WriterT SideData (State IdentState) (a, SideData))
-> WriterT SideData (State IdentState) (a, SideData)
-> WriterT SideData (State IdentState) (a, SideData)
forall a b. (a -> b) -> a -> b
$ WriterT SideData (State IdentState) a
-> WriterT SideData (State IdentState) (a, SideData)
forall (m :: * -> *) w a.
Monad m =>
WriterT w m a -> WriterT w m (a, w)
W.listen (WriterT SideData (State IdentState) a
 -> WriterT SideData (State IdentState) (a, SideData))
-> WriterT SideData (State IdentState) a
-> WriterT SideData (State IdentState) (a, SideData)
forall a b. (a -> b) -> a -> b
$ SqlQuery a -> WriterT SideData (State IdentState) a
forall a. SqlQuery a -> WriterT SideData (State IdentState) a
unQ SqlQuery a
subquery
          a'
aliasedValue <- a -> SqlQuery (ToAliasT a)
forall a. ToAlias a => a -> SqlQuery (ToAliasT a)
toAlias a
ret
          -- Make a fake query with the aliased results, this allows us to ensure that the query is only run once
          let aliasedQuery :: SqlQuery a'
aliasedQuery = WriterT SideData (State IdentState) a' -> SqlQuery a'
forall a. WriterT SideData (State IdentState) a -> SqlQuery a
Q (WriterT SideData (State IdentState) a' -> SqlQuery a')
-> WriterT SideData (State IdentState) a' -> SqlQuery a'
forall a b. (a -> b) -> a -> b
$ State IdentState (a', SideData)
-> WriterT SideData (State IdentState) a'
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
W.WriterT (State IdentState (a', SideData)
 -> WriterT SideData (State IdentState) a')
-> State IdentState (a', SideData)
-> WriterT SideData (State IdentState) a'
forall a b. (a -> b) -> a -> b
$ (a', SideData) -> State IdentState (a', SideData)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a'
aliasedValue, SideData
sideData)
          -- Add the FromQuery that renders the subquery to our side data
          Ident
subqueryAlias <- DBName -> SqlQuery Ident
newIdentFor (Text -> DBName
DBName Text
"q")
          -- Pass the aliased results of the subquery to the outer query
          -- create aliased references from the outer query results (e.g value from subquery will be `subquery`.`value`),
          -- this is probably overkill as the aliases should already be unique but seems to be good practice.
          a
ref <- Ident -> a' -> SqlQuery (ToAliasReferenceT a')
forall a.
ToAliasReference a =>
Ident -> a -> SqlQuery (ToAliasReferenceT a)
toAliasReference Ident
subqueryAlias a'
aliasedValue
          (a, FromClause) -> SqlQuery (a, FromClause)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a
ref , Ident -> (IdentInfo -> (Builder, [PersistValue])) -> FromClause
FromQuery Ident
subqueryAlias (\IdentInfo
info -> Mode -> IdentInfo -> SqlQuery a' -> (Builder, [PersistValue])
forall a r backend.
(SqlSelect a r, BackendCompatible SqlBackend backend) =>
Mode
-> (backend, IdentState) -> SqlQuery a -> (Builder, [PersistValue])
toRawSql Mode
SELECT IdentInfo
info SqlQuery a'
aliasedQuery))

      runFrom (SqlSetOperation SqlSetOperation a
operation) = do
          (SqlSetOperation a'
aliasedOperation, a'
ret) <- SqlSetOperation a
-> SqlQuery (SqlSetOperation (ToAliasT a), ToAliasT a)
forall a.
ToAlias a =>
SqlSetOperation a
-> SqlQuery (SqlSetOperation (ToAliasT a), ToAliasT a)
aliasQueries SqlSetOperation a
operation
          Ident
ident <- DBName -> SqlQuery Ident
newIdentFor (Text -> DBName
DBName Text
"u")
          a
ref <- Ident -> a' -> SqlQuery (ToAliasReferenceT a')
forall a.
ToAliasReference a =>
Ident -> a -> SqlQuery (ToAliasReferenceT a)
toAliasReference Ident
ident a'
ret
          (a, FromClause) -> SqlQuery (a, FromClause)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a
ref, Ident -> (IdentInfo -> (Builder, [PersistValue])) -> FromClause
FromQuery Ident
ident ((IdentInfo -> (Builder, [PersistValue])) -> FromClause)
-> (IdentInfo -> (Builder, [PersistValue])) -> FromClause
forall a b. (a -> b) -> a -> b
$ SqlSetOperation a' -> IdentInfo -> (Builder, [PersistValue])
forall a r backend.
(SqlSelect a r, BackendCompatible SqlBackend backend) =>
SqlSetOperation a
-> (backend, IdentState) -> (Builder, [PersistValue])
operationToSql SqlSetOperation a'
aliasedOperation)

          where
            aliasQueries :: SqlSetOperation a
-> SqlQuery (SqlSetOperation (ToAliasT a), ToAliasT a)
aliasQueries SqlSetOperation a
o =
              case SqlSetOperation a
o of
                SelectQueryP NeedParens
p SqlQuery a
q -> do
                  (a
ret, SideData
sideData) <- WriterT SideData (State IdentState) (a, SideData)
-> SqlQuery (a, SideData)
forall a. WriterT SideData (State IdentState) a -> SqlQuery a
Q (WriterT SideData (State IdentState) (a, SideData)
 -> SqlQuery (a, SideData))
-> WriterT SideData (State IdentState) (a, SideData)
-> SqlQuery (a, SideData)
forall a b. (a -> b) -> a -> b
$ (SideData -> SideData)
-> WriterT SideData (State IdentState) (a, SideData)
-> WriterT SideData (State IdentState) (a, SideData)
forall (m :: * -> *) w a.
Monad m =>
(w -> w) -> WriterT w m a -> WriterT w m a
W.censor (\SideData
_ -> SideData
forall a. Monoid a => a
mempty) (WriterT SideData (State IdentState) (a, SideData)
 -> WriterT SideData (State IdentState) (a, SideData))
-> WriterT SideData (State IdentState) (a, SideData)
-> WriterT SideData (State IdentState) (a, SideData)
forall a b. (a -> b) -> a -> b
$ WriterT SideData (State IdentState) a
-> WriterT SideData (State IdentState) (a, SideData)
forall (m :: * -> *) w a.
Monad m =>
WriterT w m a -> WriterT w m (a, w)
W.listen (WriterT SideData (State IdentState) a
 -> WriterT SideData (State IdentState) (a, SideData))
-> WriterT SideData (State IdentState) a
-> WriterT SideData (State IdentState) (a, SideData)
forall a b. (a -> b) -> a -> b
$ SqlQuery a -> WriterT SideData (State IdentState) a
forall a. SqlQuery a -> WriterT SideData (State IdentState) a
unQ SqlQuery a
q
                  IdentState
prevState <- WriterT SideData (State IdentState) IdentState
-> SqlQuery IdentState
forall a. WriterT SideData (State IdentState) a -> SqlQuery a
Q (WriterT SideData (State IdentState) IdentState
 -> SqlQuery IdentState)
-> WriterT SideData (State IdentState) IdentState
-> SqlQuery IdentState
forall a b. (a -> b) -> a -> b
$ StateT IdentState Identity IdentState
-> WriterT SideData (State IdentState) IdentState
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift StateT IdentState Identity IdentState
forall (m :: * -> *) s. Monad m => StateT s m s
S.get
                  ToAliasT a
aliasedRet <- a -> SqlQuery (ToAliasT a)
forall a. ToAlias a => a -> SqlQuery (ToAliasT a)
toAlias a
ret
                  WriterT SideData (State IdentState) () -> SqlQuery ()
forall a. WriterT SideData (State IdentState) a -> SqlQuery a
Q (WriterT SideData (State IdentState) () -> SqlQuery ())
-> WriterT SideData (State IdentState) () -> SqlQuery ()
forall a b. (a -> b) -> a -> b
$ StateT IdentState Identity ()
-> WriterT SideData (State IdentState) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (StateT IdentState Identity ()
 -> WriterT SideData (State IdentState) ())
-> StateT IdentState Identity ()
-> WriterT SideData (State IdentState) ()
forall a b. (a -> b) -> a -> b
$ IdentState -> StateT IdentState Identity ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
S.put IdentState
prevState
                  let p' :: NeedParens
p' =
                        case NeedParens
p of
                          NeedParens
Parens -> NeedParens
Parens
                          NeedParens
Never ->
                            if (SideData -> LimitClause
sdLimitClause SideData
sideData) LimitClause -> LimitClause -> Bool
forall a. Eq a => a -> a -> Bool
/= LimitClause
forall a. Monoid a => a
mempty
                                Bool -> Bool -> Bool
|| [OrderByClause] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (SideData -> [OrderByClause]
sdOrderByClause SideData
sideData) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then
                              NeedParens
Parens
                            else
                              NeedParens
Never
                  (SqlSetOperation (ToAliasT a), ToAliasT a)
-> SqlQuery (SqlSetOperation (ToAliasT a), ToAliasT a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (NeedParens -> SqlQuery (ToAliasT a) -> SqlSetOperation (ToAliasT a)
forall a. NeedParens -> SqlQuery a -> SqlSetOperation a
SelectQueryP NeedParens
p' (SqlQuery (ToAliasT a) -> SqlSetOperation (ToAliasT a))
-> SqlQuery (ToAliasT a) -> SqlSetOperation (ToAliasT a)
forall a b. (a -> b) -> a -> b
$ WriterT SideData (State IdentState) (ToAliasT a)
-> SqlQuery (ToAliasT a)
forall a. WriterT SideData (State IdentState) a -> SqlQuery a
Q (WriterT SideData (State IdentState) (ToAliasT a)
 -> SqlQuery (ToAliasT a))
-> WriterT SideData (State IdentState) (ToAliasT a)
-> SqlQuery (ToAliasT a)
forall a b. (a -> b) -> a -> b
$ State IdentState (ToAliasT a, SideData)
-> WriterT SideData (State IdentState) (ToAliasT a)
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
W.WriterT (State IdentState (ToAliasT a, SideData)
 -> WriterT SideData (State IdentState) (ToAliasT a))
-> State IdentState (ToAliasT a, SideData)
-> WriterT SideData (State IdentState) (ToAliasT a)
forall a b. (a -> b) -> a -> b
$ (ToAliasT a, SideData) -> State IdentState (ToAliasT a, SideData)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ToAliasT a
aliasedRet, SideData
sideData), ToAliasT a
aliasedRet)
                Union     SqlSetOperation a
o1 SqlSetOperation a
o2 -> do
                  (SqlSetOperation (ToAliasT a)
o1', ToAliasT a
ret) <- SqlSetOperation a
-> SqlQuery (SqlSetOperation (ToAliasT a), ToAliasT a)
aliasQueries SqlSetOperation a
o1
                  (SqlSetOperation (ToAliasT a)
o2', ToAliasT a
_  ) <- SqlSetOperation a
-> SqlQuery (SqlSetOperation (ToAliasT a), ToAliasT a)
aliasQueries SqlSetOperation a
o2
                  (SqlSetOperation (ToAliasT a), ToAliasT a)
-> SqlQuery (SqlSetOperation (ToAliasT a), ToAliasT a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlSetOperation (ToAliasT a)
-> SqlSetOperation (ToAliasT a) -> SqlSetOperation (ToAliasT a)
forall a.
SqlSetOperation a -> SqlSetOperation a -> SqlSetOperation a
Union SqlSetOperation (ToAliasT a)
o1' SqlSetOperation (ToAliasT a)
o2', ToAliasT a
ret)
                UnionAll  SqlSetOperation a
o1 SqlSetOperation a
o2 -> do
                  (SqlSetOperation (ToAliasT a)
o1', ToAliasT a
ret) <- SqlSetOperation a
-> SqlQuery (SqlSetOperation (ToAliasT a), ToAliasT a)
aliasQueries SqlSetOperation a
o1
                  (SqlSetOperation (ToAliasT a)
o2', ToAliasT a
_  ) <- SqlSetOperation a
-> SqlQuery (SqlSetOperation (ToAliasT a), ToAliasT a)
aliasQueries SqlSetOperation a
o2
                  (SqlSetOperation (ToAliasT a), ToAliasT a)
-> SqlQuery (SqlSetOperation (ToAliasT a), ToAliasT a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlSetOperation (ToAliasT a)
-> SqlSetOperation (ToAliasT a) -> SqlSetOperation (ToAliasT a)
forall a.
SqlSetOperation a -> SqlSetOperation a -> SqlSetOperation a
UnionAll SqlSetOperation (ToAliasT a)
o1' SqlSetOperation (ToAliasT a)
o2', ToAliasT a
ret)
                Except    SqlSetOperation a
o1 SqlSetOperation a
o2 -> do
                  (SqlSetOperation (ToAliasT a)
o1', ToAliasT a
ret) <- SqlSetOperation a
-> SqlQuery (SqlSetOperation (ToAliasT a), ToAliasT a)
aliasQueries SqlSetOperation a
o1
                  (SqlSetOperation (ToAliasT a)
o2', ToAliasT a
_  ) <- SqlSetOperation a
-> SqlQuery (SqlSetOperation (ToAliasT a), ToAliasT a)
aliasQueries SqlSetOperation a
o2
                  (SqlSetOperation (ToAliasT a), ToAliasT a)
-> SqlQuery (SqlSetOperation (ToAliasT a), ToAliasT a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlSetOperation (ToAliasT a)
-> SqlSetOperation (ToAliasT a) -> SqlSetOperation (ToAliasT a)
forall a.
SqlSetOperation a -> SqlSetOperation a -> SqlSetOperation a
Except SqlSetOperation (ToAliasT a)
o1' SqlSetOperation (ToAliasT a)
o2', ToAliasT a
ret)
                Intersect SqlSetOperation a
o1 SqlSetOperation a
o2 -> do
                  (SqlSetOperation (ToAliasT a)
o1', ToAliasT a
ret) <- SqlSetOperation a
-> SqlQuery (SqlSetOperation (ToAliasT a), ToAliasT a)
aliasQueries SqlSetOperation a
o1
                  (SqlSetOperation (ToAliasT a)
o2', ToAliasT a
_  ) <- SqlSetOperation a
-> SqlQuery (SqlSetOperation (ToAliasT a), ToAliasT a)
aliasQueries SqlSetOperation a
o2
                  (SqlSetOperation (ToAliasT a), ToAliasT a)
-> SqlQuery (SqlSetOperation (ToAliasT a), ToAliasT a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlSetOperation (ToAliasT a)
-> SqlSetOperation (ToAliasT a) -> SqlSetOperation (ToAliasT a)
forall a.
SqlSetOperation a -> SqlSetOperation a -> SqlSetOperation a
Intersect SqlSetOperation (ToAliasT a)
o1' SqlSetOperation (ToAliasT a)
o2', ToAliasT a
ret)

            operationToSql :: SqlSetOperation a
-> (backend, IdentState) -> (Builder, [PersistValue])
operationToSql SqlSetOperation a
o (backend, IdentState)
info =
              case SqlSetOperation a
o of
                SelectQueryP NeedParens
p SqlQuery a
q  ->
                  let (Builder
builder, [PersistValue]
values) = Mode
-> (backend, IdentState) -> SqlQuery a -> (Builder, [PersistValue])
forall a r backend.
(SqlSelect a r, BackendCompatible SqlBackend backend) =>
Mode
-> (backend, IdentState) -> SqlQuery a -> (Builder, [PersistValue])
toRawSql Mode
SELECT (backend, IdentState)
info SqlQuery a
q
                  in (NeedParens -> Builder -> Builder
parensM NeedParens
p Builder
builder, [PersistValue]
values)
                Union     SqlSetOperation a
o1 SqlSetOperation a
o2 -> Builder
-> (backend, IdentState)
-> SqlSetOperation a
-> SqlSetOperation a
-> (Builder, [PersistValue])
doSetOperation Builder
"UNION"     (backend, IdentState)
info SqlSetOperation a
o1 SqlSetOperation a
o2
                UnionAll  SqlSetOperation a
o1 SqlSetOperation a
o2 -> Builder
-> (backend, IdentState)
-> SqlSetOperation a
-> SqlSetOperation a
-> (Builder, [PersistValue])
doSetOperation Builder
"UNION ALL" (backend, IdentState)
info SqlSetOperation a
o1 SqlSetOperation a
o2
                Except    SqlSetOperation a
o1 SqlSetOperation a
o2 -> Builder
-> (backend, IdentState)
-> SqlSetOperation a
-> SqlSetOperation a
-> (Builder, [PersistValue])
doSetOperation Builder
"EXCEPT"    (backend, IdentState)
info SqlSetOperation a
o1 SqlSetOperation a
o2
                Intersect SqlSetOperation a
o1 SqlSetOperation a
o2 -> Builder
-> (backend, IdentState)
-> SqlSetOperation a
-> SqlSetOperation a
-> (Builder, [PersistValue])
doSetOperation Builder
"INTERSECT" (backend, IdentState)
info SqlSetOperation a
o1 SqlSetOperation a
o2

            doSetOperation :: Builder
-> (backend, IdentState)
-> SqlSetOperation a
-> SqlSetOperation a
-> (Builder, [PersistValue])
doSetOperation Builder
operationText (backend, IdentState)
info SqlSetOperation a
o1 SqlSetOperation a
o2 =
                  let
                    (Builder
q1, [PersistValue]
v1) = SqlSetOperation a
-> (backend, IdentState) -> (Builder, [PersistValue])
operationToSql SqlSetOperation a
o1 (backend, IdentState)
info
                    (Builder
q2, [PersistValue]
v2) = SqlSetOperation a
-> (backend, IdentState) -> (Builder, [PersistValue])
operationToSql SqlSetOperation a
o2 (backend, IdentState)
info
                  in (Builder
q1 Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
" " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
operationText Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
" " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
q2, [PersistValue]
v1 [PersistValue] -> [PersistValue] -> [PersistValue]
forall a. Semigroup a => a -> a -> a
<> [PersistValue]
v2)


      runFrom (InnerJoinFrom From a
leftPart (From b
rightPart, (a :& b) -> SqlExpr (Value Bool)
on')) = do
        (a
leftVal, FromClause
leftFrom) <- From a -> SqlQuery (a, FromClause)
forall a. From a -> SqlQuery (a, FromClause)
runFrom From a
leftPart
        (b
rightVal, FromClause
rightFrom) <- From b -> SqlQuery (b, FromClause)
forall a. From a -> SqlQuery (a, FromClause)
runFrom From b
rightPart
        let ret :: a :& b
ret = a
leftVal a -> b -> a :& b
forall a b. a -> b -> a :& b
:& b
rightVal
        (a :& b, FromClause) -> SqlQuery (a :& b, FromClause)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((a :& b, FromClause) -> SqlQuery (a :& b, FromClause))
-> (a :& b, FromClause) -> SqlQuery (a :& b, FromClause)
forall a b. (a -> b) -> a -> b
$ (a :& b
ret, FromClause
-> JoinKind
-> FromClause
-> Maybe (SqlExpr (Value Bool))
-> FromClause
FromJoin FromClause
leftFrom JoinKind
InnerJoinKind FromClause
rightFrom (SqlExpr (Value Bool) -> Maybe (SqlExpr (Value Bool))
forall a. a -> Maybe a
Just ((a :& b) -> SqlExpr (Value Bool)
on' a :& b
ret)))
      runFrom (CrossJoinFrom From a
leftPart From b
rightPart) = do
        (a
leftVal, FromClause
leftFrom) <- From a -> SqlQuery (a, FromClause)
forall a. From a -> SqlQuery (a, FromClause)
runFrom From a
leftPart
        (b
rightVal, FromClause
rightFrom) <- From b -> SqlQuery (b, FromClause)
forall a. From a -> SqlQuery (a, FromClause)
runFrom From b
rightPart
        let ret :: a :& b
ret = a
leftVal a -> b -> a :& b
forall a b. a -> b -> a :& b
:& b
rightVal
        (a :& b, FromClause) -> SqlQuery (a :& b, FromClause)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((a :& b, FromClause) -> SqlQuery (a :& b, FromClause))
-> (a :& b, FromClause) -> SqlQuery (a :& b, FromClause)
forall a b. (a -> b) -> a -> b
$ (a :& b
ret, FromClause
-> JoinKind
-> FromClause
-> Maybe (SqlExpr (Value Bool))
-> FromClause
FromJoin FromClause
leftFrom JoinKind
CrossJoinKind FromClause
rightFrom Maybe (SqlExpr (Value Bool))
forall a. Maybe a
Nothing)
      runFrom (LeftJoinFrom From a
leftPart (From b
rightPart, (a :& ToMaybeT b) -> SqlExpr (Value Bool)
on')) = do
        (a
leftVal, FromClause
leftFrom) <- From a -> SqlQuery (a, FromClause)
forall a. From a -> SqlQuery (a, FromClause)
runFrom From a
leftPart
        (b
rightVal, FromClause
rightFrom) <- From b -> SqlQuery (b, FromClause)
forall a. From a -> SqlQuery (a, FromClause)
runFrom From b
rightPart
        let ret :: a :& ToMaybeT b
ret = a
leftVal a -> ToMaybeT b -> a :& ToMaybeT b
forall a b. a -> b -> a :& b
:& (b -> ToMaybeT b
forall a. ToMaybe a => a -> ToMaybeT a
toMaybe b
rightVal)
        (a :& ToMaybeT b, FromClause)
-> SqlQuery (a :& ToMaybeT b, FromClause)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((a :& ToMaybeT b, FromClause)
 -> SqlQuery (a :& ToMaybeT b, FromClause))
-> (a :& ToMaybeT b, FromClause)
-> SqlQuery (a :& ToMaybeT b, FromClause)
forall a b. (a -> b) -> a -> b
$ (a :& ToMaybeT b
ret, FromClause
-> JoinKind
-> FromClause
-> Maybe (SqlExpr (Value Bool))
-> FromClause
FromJoin FromClause
leftFrom JoinKind
LeftOuterJoinKind FromClause
rightFrom (SqlExpr (Value Bool) -> Maybe (SqlExpr (Value Bool))
forall a. a -> Maybe a
Just ((a :& ToMaybeT b) -> SqlExpr (Value Bool)
on' a :& ToMaybeT b
ret)))
      runFrom (RightJoinFrom From a
leftPart (From b
rightPart, (ToMaybeT a :& b) -> SqlExpr (Value Bool)
on')) = do
        (a
leftVal, FromClause
leftFrom) <- From a -> SqlQuery (a, FromClause)
forall a. From a -> SqlQuery (a, FromClause)
runFrom From a
leftPart
        (b
rightVal, FromClause
rightFrom) <- From b -> SqlQuery (b, FromClause)
forall a. From a -> SqlQuery (a, FromClause)
runFrom From b
rightPart
        let ret :: ToMaybeT a :& b
ret = (a -> ToMaybeT a
forall a. ToMaybe a => a -> ToMaybeT a
toMaybe a
leftVal) ToMaybeT a -> b -> ToMaybeT a :& b
forall a b. a -> b -> a :& b
:& b
rightVal
        (ToMaybeT a :& b, FromClause)
-> SqlQuery (ToMaybeT a :& b, FromClause)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((ToMaybeT a :& b, FromClause)
 -> SqlQuery (ToMaybeT a :& b, FromClause))
-> (ToMaybeT a :& b, FromClause)
-> SqlQuery (ToMaybeT a :& b, FromClause)
forall a b. (a -> b) -> a -> b
$ (ToMaybeT a :& b
ret, FromClause
-> JoinKind
-> FromClause
-> Maybe (SqlExpr (Value Bool))
-> FromClause
FromJoin FromClause
leftFrom JoinKind
RightOuterJoinKind FromClause
rightFrom (SqlExpr (Value Bool) -> Maybe (SqlExpr (Value Bool))
forall a. a -> Maybe a
Just ((ToMaybeT a :& b) -> SqlExpr (Value Bool)
on' ToMaybeT a :& b
ret)))
      runFrom (FullJoinFrom From a
leftPart (From b
rightPart, (ToMaybeT a :& ToMaybeT b) -> SqlExpr (Value Bool)
on')) = do
        (a
leftVal, FromClause
leftFrom) <- From a -> SqlQuery (a, FromClause)
forall a. From a -> SqlQuery (a, FromClause)
runFrom From a
leftPart
        (b
rightVal, FromClause
rightFrom) <- From b -> SqlQuery (b, FromClause)
forall a. From a -> SqlQuery (a, FromClause)
runFrom From b
rightPart
        let ret :: ToMaybeT a :& ToMaybeT b
ret = (a -> ToMaybeT a
forall a. ToMaybe a => a -> ToMaybeT a
toMaybe a
leftVal) ToMaybeT a -> ToMaybeT b -> ToMaybeT a :& ToMaybeT b
forall a b. a -> b -> a :& b
:& (b -> ToMaybeT b
forall a. ToMaybe a => a -> ToMaybeT a
toMaybe b
rightVal)
        (ToMaybeT a :& ToMaybeT b, FromClause)
-> SqlQuery (ToMaybeT a :& ToMaybeT b, FromClause)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((ToMaybeT a :& ToMaybeT b, FromClause)
 -> SqlQuery (ToMaybeT a :& ToMaybeT b, FromClause))
-> (ToMaybeT a :& ToMaybeT b, FromClause)
-> SqlQuery (ToMaybeT a :& ToMaybeT b, FromClause)
forall a b. (a -> b) -> a -> b
$ (ToMaybeT a :& ToMaybeT b
ret, FromClause
-> JoinKind
-> FromClause
-> Maybe (SqlExpr (Value Bool))
-> FromClause
FromJoin FromClause
leftFrom JoinKind
FullOuterJoinKind FromClause
rightFrom (SqlExpr (Value Bool) -> Maybe (SqlExpr (Value Bool))
forall a. a -> Maybe a
Just ((ToMaybeT a :& ToMaybeT b) -> SqlExpr (Value Bool)
on' ToMaybeT a :& ToMaybeT b
ret)))

type family ToAliasT a where
  ToAliasT (SqlExpr (Value a)) = SqlExpr (Value a)
  ToAliasT (SqlExpr (Entity a)) = SqlExpr (Entity a)
  ToAliasT (SqlExpr (Maybe (Entity a))) = SqlExpr (Maybe (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)

-- Tedious tuple magic
class ToAlias a where
  toAlias :: a -> SqlQuery (ToAliasT a)

instance ToAlias (SqlExpr (Value a)) where
  toAlias :: SqlExpr (Value a) -> SqlQuery (ToAliasT (SqlExpr (Value a)))
toAlias v :: SqlExpr (Value a)
v@(EAliasedValue Ident
_ SqlExpr (Value a)
_) = SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a))
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlExpr (Value a)
v
  toAlias SqlExpr (Value a)
v = do
    Ident
ident <- DBName -> SqlQuery Ident
newIdentFor (Text -> DBName
DBName Text
"v")
    SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a)))
-> SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a))
forall a b. (a -> b) -> a -> b
$ Ident -> SqlExpr (Value a) -> SqlExpr (Value a)
forall a. Ident -> SqlExpr (Value a) -> SqlExpr (Value a)
EAliasedValue Ident
ident SqlExpr (Value a)
v

instance ToAlias (SqlExpr (Entity a)) where
  toAlias :: SqlExpr (Entity a) -> SqlQuery (ToAliasT (SqlExpr (Entity a)))
toAlias v :: SqlExpr (Entity a)
v@(EAliasedEntityReference Ident
_ Ident
_) = SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a))
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlExpr (Entity a)
v
  toAlias v :: SqlExpr (Entity a)
v@(EAliasedEntity Ident
_ Ident
_) = SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a))
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlExpr (Entity a)
v
  toAlias (EEntity Ident
tableIdent) = do
    Ident
ident <- DBName -> SqlQuery Ident
newIdentFor (Text -> DBName
DBName Text
"v")
    SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a)))
-> SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a))
forall a b. (a -> b) -> a -> b
$ Ident -> Ident -> SqlExpr (Entity a)
forall val. Ident -> Ident -> SqlExpr (Entity val)
EAliasedEntity Ident
ident Ident
tableIdent

instance ToAlias (SqlExpr (Maybe (Entity a))) where
  toAlias :: SqlExpr (Maybe (Entity a))
-> SqlQuery (ToAliasT (SqlExpr (Maybe (Entity a))))
toAlias (EMaybe SqlExpr a
e) = SqlExpr (Entity a) -> SqlExpr (Maybe (Entity a))
forall a. SqlExpr a -> SqlExpr (Maybe a)
EMaybe (SqlExpr (Entity a) -> SqlExpr (Maybe (Entity a)))
-> SqlQuery (SqlExpr (Entity a))
-> SqlQuery (SqlExpr (Maybe (Entity a)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SqlExpr a -> SqlQuery (ToAliasT (SqlExpr a))
forall a. ToAlias a => a -> SqlQuery (ToAliasT a)
toAlias SqlExpr a
e

instance (ToAlias a, ToAlias b) => ToAlias (a,b) where
  toAlias :: (a, b) -> SqlQuery (ToAliasT (a, b))
toAlias (a
a,b
b) = (,) (ToAliasT a -> ToAliasT b -> (ToAliasT a, ToAliasT b))
-> SqlQuery (ToAliasT a)
-> SqlQuery (ToAliasT b -> (ToAliasT a, ToAliasT b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> SqlQuery (ToAliasT a)
forall a. ToAlias a => a -> SqlQuery (ToAliasT a)
toAlias a
a SqlQuery (ToAliasT b -> (ToAliasT a, ToAliasT b))
-> SqlQuery (ToAliasT b) -> SqlQuery (ToAliasT a, ToAliasT b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> SqlQuery (ToAliasT b)
forall a. ToAlias a => a -> SqlQuery (ToAliasT a)
toAlias b
b

instance ( ToAlias a
         , ToAlias b
         , ToAlias c
         ) => ToAlias (a,b,c) where
  toAlias :: (a, b, c) -> SqlQuery (ToAliasT (a, b, c))
toAlias (a, b, c)
x = ((ToAliasT a, ToAliasT b), ToAliasT c)
-> (ToAliasT a, ToAliasT b, ToAliasT c)
forall a b c. ((a, b), c) -> (a, b, c)
to3 (((ToAliasT a, ToAliasT b), ToAliasT c)
 -> (ToAliasT a, ToAliasT b, ToAliasT c))
-> SqlQuery ((ToAliasT a, ToAliasT b), ToAliasT c)
-> SqlQuery (ToAliasT a, ToAliasT b, ToAliasT c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (((a, b), c) -> SqlQuery (ToAliasT ((a, b), c))
forall a. ToAlias a => a -> SqlQuery (ToAliasT a)
toAlias (((a, b), c) -> SqlQuery (ToAliasT ((a, b), c)))
-> ((a, b), c) -> SqlQuery (ToAliasT ((a, b), c))
forall a b. (a -> b) -> a -> b
$ (a, b, c) -> ((a, b), c)
forall a b c. (a, b, c) -> ((a, b), c)
from3 (a, b, c)
x)

instance ( ToAlias a
         , ToAlias b
         , ToAlias c
         , ToAlias d
         ) => ToAlias (a,b,c,d) where
  toAlias :: (a, b, c, d) -> SqlQuery (ToAliasT (a, b, c, d))
toAlias (a, b, c, d)
x = ((ToAliasT a, ToAliasT b), (ToAliasT c, ToAliasT d))
-> (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d)
forall a b c d. ((a, b), (c, d)) -> (a, b, c, d)
to4 (((ToAliasT a, ToAliasT b), (ToAliasT c, ToAliasT d))
 -> (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d))
-> SqlQuery ((ToAliasT a, ToAliasT b), (ToAliasT c, ToAliasT d))
-> SqlQuery (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (((a, b), (c, d)) -> SqlQuery (ToAliasT ((a, b), (c, d)))
forall a. ToAlias a => a -> SqlQuery (ToAliasT a)
toAlias (((a, b), (c, d)) -> SqlQuery (ToAliasT ((a, b), (c, d))))
-> ((a, b), (c, d)) -> SqlQuery (ToAliasT ((a, b), (c, d)))
forall a b. (a -> b) -> a -> b
$ (a, b, c, d) -> ((a, b), (c, d))
forall a b c d. (a, b, c, d) -> ((a, b), (c, d))
from4 (a, b, c, d)
x)

instance ( ToAlias a
         , ToAlias b
         , ToAlias c
         , ToAlias d
         , ToAlias e
         ) => ToAlias (a,b,c,d,e) where
  toAlias :: (a, b, c, d, e) -> SqlQuery (ToAliasT (a, b, c, d, e))
toAlias (a, b, c, d, e)
x = ((ToAliasT a, ToAliasT b), (ToAliasT c, ToAliasT d), ToAliasT e)
-> (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e)
forall a b c d e. ((a, b), (c, d), e) -> (a, b, c, d, e)
to5 (((ToAliasT a, ToAliasT b), (ToAliasT c, ToAliasT d), ToAliasT e)
 -> (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e))
-> SqlQuery
     ((ToAliasT a, ToAliasT b), (ToAliasT c, ToAliasT d), ToAliasT e)
-> SqlQuery
     (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (((a, b), (c, d), e) -> SqlQuery (ToAliasT ((a, b), (c, d), e))
forall a. ToAlias a => a -> SqlQuery (ToAliasT a)
toAlias (((a, b), (c, d), e) -> SqlQuery (ToAliasT ((a, b), (c, d), e)))
-> ((a, b), (c, d), e) -> SqlQuery (ToAliasT ((a, b), (c, d), e))
forall a b. (a -> b) -> a -> b
$ (a, b, c, d, e) -> ((a, b), (c, d), e)
forall a b c d e. (a, b, c, d, e) -> ((a, b), (c, d), e)
from5 (a, b, c, d, e)
x)

instance ( ToAlias a
         , ToAlias b
         , ToAlias c
         , ToAlias d
         , ToAlias e
         , ToAlias f
         ) => ToAlias (a,b,c,d,e,f) where
  toAlias :: (a, b, c, d, e, f) -> SqlQuery (ToAliasT (a, b, c, d, e, f))
toAlias (a, b, c, d, e, f)
x = ((ToAliasT a, ToAliasT b), (ToAliasT c, ToAliasT d),
 (ToAliasT e, ToAliasT f))
-> (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e,
    ToAliasT f)
forall a b c d e f. ((a, b), (c, d), (e, f)) -> (a, b, c, d, e, f)
to6 (((ToAliasT a, ToAliasT b), (ToAliasT c, ToAliasT d),
  (ToAliasT e, ToAliasT f))
 -> (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e,
     ToAliasT f))
-> SqlQuery
     ((ToAliasT a, ToAliasT b), (ToAliasT c, ToAliasT d),
      (ToAliasT e, ToAliasT f))
-> SqlQuery
     (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e,
      ToAliasT f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (((a, b), (c, d), (e, f))
-> SqlQuery (ToAliasT ((a, b), (c, d), (e, f)))
forall a. ToAlias a => a -> SqlQuery (ToAliasT a)
toAlias (((a, b), (c, d), (e, f))
 -> SqlQuery (ToAliasT ((a, b), (c, d), (e, f))))
-> ((a, b), (c, d), (e, f))
-> SqlQuery (ToAliasT ((a, b), (c, d), (e, f)))
forall a b. (a -> b) -> a -> b
$ (a, b, c, d, e, f) -> ((a, b), (c, d), (e, f))
forall a b c d e f. (a, b, c, d, e, f) -> ((a, b), (c, d), (e, f))
from6 (a, b, c, d, e, f)
x)

instance ( ToAlias a
         , ToAlias b
         , ToAlias c
         , ToAlias d
         , ToAlias e
         , ToAlias f
         , ToAlias g
         ) => ToAlias (a,b,c,d,e,f,g) where
  toAlias :: (a, b, c, d, e, f, g) -> SqlQuery (ToAliasT (a, b, c, d, e, f, g))
toAlias (a, b, c, d, e, f, g)
x = ((ToAliasT a, ToAliasT b), (ToAliasT c, ToAliasT d),
 (ToAliasT e, ToAliasT f), ToAliasT g)
-> (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e,
    ToAliasT f, ToAliasT g)
forall a b c d e f g.
((a, b), (c, d), (e, f), g) -> (a, b, c, d, e, f, g)
to7 (((ToAliasT a, ToAliasT b), (ToAliasT c, ToAliasT d),
  (ToAliasT e, ToAliasT f), ToAliasT g)
 -> (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e,
     ToAliasT f, ToAliasT g))
-> SqlQuery
     ((ToAliasT a, ToAliasT b), (ToAliasT c, ToAliasT d),
      (ToAliasT e, ToAliasT f), ToAliasT g)
-> SqlQuery
     (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e,
      ToAliasT f, ToAliasT g)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (((a, b), (c, d), (e, f), g)
-> SqlQuery (ToAliasT ((a, b), (c, d), (e, f), g))
forall a. ToAlias a => a -> SqlQuery (ToAliasT a)
toAlias (((a, b), (c, d), (e, f), g)
 -> SqlQuery (ToAliasT ((a, b), (c, d), (e, f), g)))
-> ((a, b), (c, d), (e, f), g)
-> SqlQuery (ToAliasT ((a, b), (c, d), (e, f), g))
forall a b. (a -> b) -> a -> b
$ (a, b, c, d, e, f, g) -> ((a, b), (c, d), (e, f), g)
forall a b c d e f g.
(a, b, c, d, e, f, g) -> ((a, b), (c, d), (e, f), g)
from7 (a, b, c, d, e, f, g)
x)

instance ( 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) where
  toAlias :: (a, b, c, d, e, f, g, h)
-> SqlQuery (ToAliasT (a, b, c, d, e, f, g, h))
toAlias (a, b, c, d, e, f, g, h)
x = ((ToAliasT a, ToAliasT b), (ToAliasT c, ToAliasT d),
 (ToAliasT e, ToAliasT f), (ToAliasT g, ToAliasT h))
-> (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e,
    ToAliasT f, ToAliasT g, ToAliasT h)
forall a b c d e f g h.
((a, b), (c, d), (e, f), (g, h)) -> (a, b, c, d, e, f, g, h)
to8 (((ToAliasT a, ToAliasT b), (ToAliasT c, ToAliasT d),
  (ToAliasT e, ToAliasT f), (ToAliasT g, ToAliasT h))
 -> (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e,
     ToAliasT f, ToAliasT g, ToAliasT h))
-> SqlQuery
     ((ToAliasT a, ToAliasT b), (ToAliasT c, ToAliasT d),
      (ToAliasT e, ToAliasT f), (ToAliasT g, ToAliasT h))
-> SqlQuery
     (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e,
      ToAliasT f, ToAliasT g, ToAliasT h)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (((a, b), (c, d), (e, f), (g, h))
-> SqlQuery (ToAliasT ((a, b), (c, d), (e, f), (g, h)))
forall a. ToAlias a => a -> SqlQuery (ToAliasT a)
toAlias (((a, b), (c, d), (e, f), (g, h))
 -> SqlQuery (ToAliasT ((a, b), (c, d), (e, f), (g, h))))
-> ((a, b), (c, d), (e, f), (g, h))
-> SqlQuery (ToAliasT ((a, b), (c, d), (e, f), (g, h)))
forall a b. (a -> b) -> a -> b
$ (a, b, c, d, e, f, g, h) -> ((a, b), (c, d), (e, f), (g, h))
forall a b c d e f g h.
(a, b, c, d, e, f, g, h) -> ((a, b), (c, d), (e, f), (g, h))
from8 (a, b, c, d, e, f, g, h)
x)


type family ToAliasReferenceT a where
  ToAliasReferenceT (SqlExpr (Value a)) = SqlExpr (Value a)
  ToAliasReferenceT (SqlExpr (Entity a)) = SqlExpr (Entity a)
  ToAliasReferenceT (SqlExpr (Maybe (Entity a))) = SqlExpr (Maybe (Entity a))
  ToAliasReferenceT (a,b) = (ToAliasReferenceT a, ToAliasReferenceT b)
  ToAliasReferenceT (a,b,c) = (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c)
  ToAliasReferenceT (a, b, c, d) = (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c, ToAliasReferenceT d)
  ToAliasReferenceT (a, b, c, d, e) = (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c, ToAliasReferenceT d, ToAliasReferenceT e)
  ToAliasReferenceT (a, b, c, d, e, f) = (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c, ToAliasReferenceT d, ToAliasReferenceT e, ToAliasReferenceT f)
  ToAliasReferenceT (a, b, c, d, e, f, g) = (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c, ToAliasReferenceT d, ToAliasReferenceT e, ToAliasReferenceT f, ToAliasReferenceT g)
  ToAliasReferenceT (a, b, c, d, e, f, g, h) = (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c, ToAliasReferenceT d, ToAliasReferenceT e, ToAliasReferenceT f, ToAliasReferenceT g, ToAliasReferenceT h)

-- more tedious tuple magic
class ToAliasReference a where
  toAliasReference :: Ident -> a -> SqlQuery (ToAliasReferenceT a)

instance ToAliasReference (SqlExpr (Value a)) where
  toAliasReference :: Ident
-> SqlExpr (Value a)
-> SqlQuery (ToAliasReferenceT (SqlExpr (Value a)))
toAliasReference Ident
aliasSource (EAliasedValue Ident
aliasIdent SqlExpr (Value a)
_) = SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a)))
-> SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a))
forall a b. (a -> b) -> a -> b
$ Ident -> (IdentInfo -> Ident) -> SqlExpr (Value a)
forall a. Ident -> (IdentInfo -> Ident) -> SqlExpr (Value a)
EValueReference Ident
aliasSource (\IdentInfo
_ -> Ident
aliasIdent)
  toAliasReference Ident
_           v :: SqlExpr (Value a)
v@(ERaw NeedParens
_ IdentInfo -> (Builder, [PersistValue])
_)                 = SqlExpr (Value a) -> SqlQuery (ToAliasT (SqlExpr (Value a)))
forall a. ToAlias a => a -> SqlQuery (ToAliasT a)
toAlias SqlExpr (Value a)
v
  toAliasReference Ident
_           v :: SqlExpr (Value a)
v@(ECompositeKey IdentInfo -> [Builder]
_)          = SqlExpr (Value a) -> SqlQuery (ToAliasT (SqlExpr (Value a)))
forall a. ToAlias a => a -> SqlQuery (ToAliasT a)
toAlias SqlExpr (Value a)
v
  toAliasReference Ident
s             (EValueReference Ident
_ IdentInfo -> Ident
b)      = SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a)))
-> SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a))
forall a b. (a -> b) -> a -> b
$ Ident -> (IdentInfo -> Ident) -> SqlExpr (Value a)
forall a. Ident -> (IdentInfo -> Ident) -> SqlExpr (Value a)
EValueReference Ident
s IdentInfo -> Ident
b

instance ToAliasReference (SqlExpr (Entity a)) where
  toAliasReference :: Ident
-> SqlExpr (Entity a)
-> SqlQuery (ToAliasReferenceT (SqlExpr (Entity a)))
toAliasReference Ident
aliasSource (EAliasedEntity Ident
ident Ident
_) = SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a)))
-> SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a))
forall a b. (a -> b) -> a -> b
$ Ident -> Ident -> SqlExpr (Entity a)
forall val. Ident -> Ident -> SqlExpr (Entity val)
EAliasedEntityReference Ident
aliasSource Ident
ident
  toAliasReference Ident
_ e :: SqlExpr (Entity a)
e@(EEntity Ident
_) = SqlExpr (Entity a) -> SqlQuery (ToAliasT (SqlExpr (Entity a)))
forall a. ToAlias a => a -> SqlQuery (ToAliasT a)
toAlias SqlExpr (Entity a)
e
  toAliasReference Ident
s   (EAliasedEntityReference Ident
_ Ident
b) = SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a)))
-> SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a))
forall a b. (a -> b) -> a -> b
$ Ident -> Ident -> SqlExpr (Entity a)
forall val. Ident -> Ident -> SqlExpr (Entity val)
EAliasedEntityReference Ident
s Ident
b

instance ToAliasReference (SqlExpr (Maybe (Entity a))) where
  toAliasReference :: Ident
-> SqlExpr (Maybe (Entity a))
-> SqlQuery (ToAliasReferenceT (SqlExpr (Maybe (Entity a))))
toAliasReference Ident
s (EMaybe SqlExpr a
e) = SqlExpr (Entity a) -> SqlExpr (Maybe (Entity a))
forall a. SqlExpr a -> SqlExpr (Maybe a)
EMaybe (SqlExpr (Entity a) -> SqlExpr (Maybe (Entity a)))
-> SqlQuery (SqlExpr (Entity a))
-> SqlQuery (SqlExpr (Maybe (Entity a)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ident -> SqlExpr a -> SqlQuery (ToAliasReferenceT (SqlExpr a))
forall a.
ToAliasReference a =>
Ident -> a -> SqlQuery (ToAliasReferenceT a)
toAliasReference Ident
s SqlExpr a
e
instance (ToAliasReference a, ToAliasReference b) => ToAliasReference (a, b) where
  toAliasReference :: Ident -> (a, b) -> SqlQuery (ToAliasReferenceT (a, b))
toAliasReference Ident
ident (a
a,b
b) = (,) (ToAliasReferenceT a
 -> ToAliasReferenceT b
 -> (ToAliasReferenceT a, ToAliasReferenceT b))
-> SqlQuery (ToAliasReferenceT a)
-> SqlQuery
     (ToAliasReferenceT b -> (ToAliasReferenceT a, ToAliasReferenceT b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ident -> a -> SqlQuery (ToAliasReferenceT a)
forall a.
ToAliasReference a =>
Ident -> a -> SqlQuery (ToAliasReferenceT a)
toAliasReference Ident
ident a
a) SqlQuery
  (ToAliasReferenceT b -> (ToAliasReferenceT a, ToAliasReferenceT b))
-> SqlQuery (ToAliasReferenceT b)
-> SqlQuery (ToAliasReferenceT a, ToAliasReferenceT b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Ident -> b -> SqlQuery (ToAliasReferenceT b)
forall a.
ToAliasReference a =>
Ident -> a -> SqlQuery (ToAliasReferenceT a)
toAliasReference Ident
ident b
b)

instance ( ToAliasReference a
         , ToAliasReference b
         , ToAliasReference c
         ) => ToAliasReference (a,b,c) where
  toAliasReference :: Ident -> (a, b, c) -> SqlQuery (ToAliasReferenceT (a, b, c))
toAliasReference Ident
ident (a, b, c)
x = (((ToAliasReferenceT a, ToAliasReferenceT b), ToAliasReferenceT c)
 -> (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c))
-> SqlQuery
     ((ToAliasReferenceT a, ToAliasReferenceT b), ToAliasReferenceT c)
-> SqlQuery
     (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ToAliasReferenceT a, ToAliasReferenceT b), ToAliasReferenceT c)
-> (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c)
forall a b c. ((a, b), c) -> (a, b, c)
to3 (SqlQuery
   ((ToAliasReferenceT a, ToAliasReferenceT b), ToAliasReferenceT c)
 -> SqlQuery
      (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c))
-> SqlQuery
     ((ToAliasReferenceT a, ToAliasReferenceT b), ToAliasReferenceT c)
-> SqlQuery
     (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c)
forall a b. (a -> b) -> a -> b
$ Ident -> ((a, b), c) -> SqlQuery (ToAliasReferenceT ((a, b), c))
forall a.
ToAliasReference a =>
Ident -> a -> SqlQuery (ToAliasReferenceT a)
toAliasReference Ident
ident (((a, b), c) -> SqlQuery (ToAliasReferenceT ((a, b), c)))
-> ((a, b), c) -> SqlQuery (ToAliasReferenceT ((a, b), c))
forall a b. (a -> b) -> a -> b
$ (a, b, c) -> ((a, b), c)
forall a b c. (a, b, c) -> ((a, b), c)
from3 (a, b, c)
x

instance ( ToAliasReference a
         , ToAliasReference b
         , ToAliasReference c
         , ToAliasReference d
         ) => ToAliasReference (a,b,c,d) where
  toAliasReference :: Ident -> (a, b, c, d) -> SqlQuery (ToAliasReferenceT (a, b, c, d))
toAliasReference Ident
ident (a, b, c, d)
x = (((ToAliasReferenceT a, ToAliasReferenceT b),
  (ToAliasReferenceT c, ToAliasReferenceT d))
 -> (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
     ToAliasReferenceT d))
-> SqlQuery
     ((ToAliasReferenceT a, ToAliasReferenceT b),
      (ToAliasReferenceT c, ToAliasReferenceT d))
-> SqlQuery
     (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
      ToAliasReferenceT d)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ToAliasReferenceT a, ToAliasReferenceT b),
 (ToAliasReferenceT c, ToAliasReferenceT d))
-> (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
    ToAliasReferenceT d)
forall a b c d. ((a, b), (c, d)) -> (a, b, c, d)
to4 (SqlQuery
   ((ToAliasReferenceT a, ToAliasReferenceT b),
    (ToAliasReferenceT c, ToAliasReferenceT d))
 -> SqlQuery
      (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
       ToAliasReferenceT d))
-> SqlQuery
     ((ToAliasReferenceT a, ToAliasReferenceT b),
      (ToAliasReferenceT c, ToAliasReferenceT d))
-> SqlQuery
     (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
      ToAliasReferenceT d)
forall a b. (a -> b) -> a -> b
$ Ident
-> ((a, b), (c, d))
-> SqlQuery (ToAliasReferenceT ((a, b), (c, d)))
forall a.
ToAliasReference a =>
Ident -> a -> SqlQuery (ToAliasReferenceT a)
toAliasReference Ident
ident (((a, b), (c, d)) -> SqlQuery (ToAliasReferenceT ((a, b), (c, d))))
-> ((a, b), (c, d))
-> SqlQuery (ToAliasReferenceT ((a, b), (c, d)))
forall a b. (a -> b) -> a -> b
$ (a, b, c, d) -> ((a, b), (c, d))
forall a b c d. (a, b, c, d) -> ((a, b), (c, d))
from4 (a, b, c, d)
x

instance ( ToAliasReference a
         , ToAliasReference b
         , ToAliasReference c
         , ToAliasReference d
         , ToAliasReference e
         ) => ToAliasReference (a,b,c,d,e) where
  toAliasReference :: Ident
-> (a, b, c, d, e) -> SqlQuery (ToAliasReferenceT (a, b, c, d, e))
toAliasReference Ident
ident (a, b, c, d, e)
x = (((ToAliasReferenceT a, ToAliasReferenceT b),
  (ToAliasReferenceT c, ToAliasReferenceT d), ToAliasReferenceT e)
 -> (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
     ToAliasReferenceT d, ToAliasReferenceT e))
-> SqlQuery
     ((ToAliasReferenceT a, ToAliasReferenceT b),
      (ToAliasReferenceT c, ToAliasReferenceT d), ToAliasReferenceT e)
-> SqlQuery
     (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
      ToAliasReferenceT d, ToAliasReferenceT e)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ToAliasReferenceT a, ToAliasReferenceT b),
 (ToAliasReferenceT c, ToAliasReferenceT d), ToAliasReferenceT e)
-> (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
    ToAliasReferenceT d, ToAliasReferenceT e)
forall a b c d e. ((a, b), (c, d), e) -> (a, b, c, d, e)
to5 (SqlQuery
   ((ToAliasReferenceT a, ToAliasReferenceT b),
    (ToAliasReferenceT c, ToAliasReferenceT d), ToAliasReferenceT e)
 -> SqlQuery
      (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
       ToAliasReferenceT d, ToAliasReferenceT e))
-> SqlQuery
     ((ToAliasReferenceT a, ToAliasReferenceT b),
      (ToAliasReferenceT c, ToAliasReferenceT d), ToAliasReferenceT e)
-> SqlQuery
     (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
      ToAliasReferenceT d, ToAliasReferenceT e)
forall a b. (a -> b) -> a -> b
$ Ident
-> ((a, b), (c, d), e)
-> SqlQuery (ToAliasReferenceT ((a, b), (c, d), e))
forall a.
ToAliasReference a =>
Ident -> a -> SqlQuery (ToAliasReferenceT a)
toAliasReference Ident
ident (((a, b), (c, d), e)
 -> SqlQuery (ToAliasReferenceT ((a, b), (c, d), e)))
-> ((a, b), (c, d), e)
-> SqlQuery (ToAliasReferenceT ((a, b), (c, d), e))
forall a b. (a -> b) -> a -> b
$ (a, b, c, d, e) -> ((a, b), (c, d), e)
forall a b c d e. (a, b, c, d, e) -> ((a, b), (c, d), e)
from5 (a, b, c, d, e)
x

instance ( ToAliasReference a
         , ToAliasReference b
         , ToAliasReference c
         , ToAliasReference d
         , ToAliasReference e
         , ToAliasReference f
         ) => ToAliasReference (a,b,c,d,e,f) where
  toAliasReference :: Ident
-> (a, b, c, d, e, f)
-> SqlQuery (ToAliasReferenceT (a, b, c, d, e, f))
toAliasReference Ident
ident (a, b, c, d, e, f)
x = ((ToAliasReferenceT a, ToAliasReferenceT b),
 (ToAliasReferenceT c, ToAliasReferenceT d),
 (ToAliasReferenceT e, ToAliasReferenceT f))
-> (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
    ToAliasReferenceT d, ToAliasReferenceT e, ToAliasReferenceT f)
forall a b c d e f. ((a, b), (c, d), (e, f)) -> (a, b, c, d, e, f)
to6 (((ToAliasReferenceT a, ToAliasReferenceT b),
  (ToAliasReferenceT c, ToAliasReferenceT d),
  (ToAliasReferenceT e, ToAliasReferenceT f))
 -> (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
     ToAliasReferenceT d, ToAliasReferenceT e, ToAliasReferenceT f))
-> SqlQuery
     ((ToAliasReferenceT a, ToAliasReferenceT b),
      (ToAliasReferenceT c, ToAliasReferenceT d),
      (ToAliasReferenceT e, ToAliasReferenceT f))
-> SqlQuery
     (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
      ToAliasReferenceT d, ToAliasReferenceT e, ToAliasReferenceT f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ident
-> ((a, b), (c, d), (e, f))
-> SqlQuery (ToAliasReferenceT ((a, b), (c, d), (e, f)))
forall a.
ToAliasReference a =>
Ident -> a -> SqlQuery (ToAliasReferenceT a)
toAliasReference Ident
ident (((a, b), (c, d), (e, f))
 -> SqlQuery (ToAliasReferenceT ((a, b), (c, d), (e, f))))
-> ((a, b), (c, d), (e, f))
-> SqlQuery (ToAliasReferenceT ((a, b), (c, d), (e, f)))
forall a b. (a -> b) -> a -> b
$ (a, b, c, d, e, f) -> ((a, b), (c, d), (e, f))
forall a b c d e f. (a, b, c, d, e, f) -> ((a, b), (c, d), (e, f))
from6 (a, b, c, d, e, f)
x)

instance ( ToAliasReference a
         , ToAliasReference b
         , ToAliasReference c
         , ToAliasReference d
         , ToAliasReference e
         , ToAliasReference f
         , ToAliasReference g
         ) => ToAliasReference (a,b,c,d,e,f,g) where
  toAliasReference :: Ident
-> (a, b, c, d, e, f, g)
-> SqlQuery (ToAliasReferenceT (a, b, c, d, e, f, g))
toAliasReference Ident
ident (a, b, c, d, e, f, g)
x = ((ToAliasReferenceT a, ToAliasReferenceT b),
 (ToAliasReferenceT c, ToAliasReferenceT d),
 (ToAliasReferenceT e, ToAliasReferenceT f), ToAliasReferenceT g)
-> (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
    ToAliasReferenceT d, ToAliasReferenceT e, ToAliasReferenceT f,
    ToAliasReferenceT g)
forall a b c d e f g.
((a, b), (c, d), (e, f), g) -> (a, b, c, d, e, f, g)
to7 (((ToAliasReferenceT a, ToAliasReferenceT b),
  (ToAliasReferenceT c, ToAliasReferenceT d),
  (ToAliasReferenceT e, ToAliasReferenceT f), ToAliasReferenceT g)
 -> (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
     ToAliasReferenceT d, ToAliasReferenceT e, ToAliasReferenceT f,
     ToAliasReferenceT g))
-> SqlQuery
     ((ToAliasReferenceT a, ToAliasReferenceT b),
      (ToAliasReferenceT c, ToAliasReferenceT d),
      (ToAliasReferenceT e, ToAliasReferenceT f), ToAliasReferenceT g)
-> SqlQuery
     (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
      ToAliasReferenceT d, ToAliasReferenceT e, ToAliasReferenceT f,
      ToAliasReferenceT g)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ident
-> ((a, b), (c, d), (e, f), g)
-> SqlQuery (ToAliasReferenceT ((a, b), (c, d), (e, f), g))
forall a.
ToAliasReference a =>
Ident -> a -> SqlQuery (ToAliasReferenceT a)
toAliasReference Ident
ident (((a, b), (c, d), (e, f), g)
 -> SqlQuery (ToAliasReferenceT ((a, b), (c, d), (e, f), g)))
-> ((a, b), (c, d), (e, f), g)
-> SqlQuery (ToAliasReferenceT ((a, b), (c, d), (e, f), g))
forall a b. (a -> b) -> a -> b
$ (a, b, c, d, e, f, g) -> ((a, b), (c, d), (e, f), g)
forall a b c d e f g.
(a, b, c, d, e, f, g) -> ((a, b), (c, d), (e, f), g)
from7 (a, b, c, d, e, f, g)
x)

instance ( ToAliasReference a
         , ToAliasReference b
         , ToAliasReference c
         , ToAliasReference d
         , ToAliasReference e
         , ToAliasReference f
         , ToAliasReference g
         , ToAliasReference h
         ) => ToAliasReference (a,b,c,d,e,f,g,h) where
  toAliasReference :: Ident
-> (a, b, c, d, e, f, g, h)
-> SqlQuery (ToAliasReferenceT (a, b, c, d, e, f, g, h))
toAliasReference Ident
ident (a, b, c, d, e, f, g, h)
x = ((ToAliasReferenceT a, ToAliasReferenceT b),
 (ToAliasReferenceT c, ToAliasReferenceT d),
 (ToAliasReferenceT e, ToAliasReferenceT f),
 (ToAliasReferenceT g, ToAliasReferenceT h))
-> (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
    ToAliasReferenceT d, ToAliasReferenceT e, ToAliasReferenceT f,
    ToAliasReferenceT g, ToAliasReferenceT h)
forall a b c d e f g h.
((a, b), (c, d), (e, f), (g, h)) -> (a, b, c, d, e, f, g, h)
to8 (((ToAliasReferenceT a, ToAliasReferenceT b),
  (ToAliasReferenceT c, ToAliasReferenceT d),
  (ToAliasReferenceT e, ToAliasReferenceT f),
  (ToAliasReferenceT g, ToAliasReferenceT h))
 -> (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
     ToAliasReferenceT d, ToAliasReferenceT e, ToAliasReferenceT f,
     ToAliasReferenceT g, ToAliasReferenceT h))
-> SqlQuery
     ((ToAliasReferenceT a, ToAliasReferenceT b),
      (ToAliasReferenceT c, ToAliasReferenceT d),
      (ToAliasReferenceT e, ToAliasReferenceT f),
      (ToAliasReferenceT g, ToAliasReferenceT h))
-> SqlQuery
     (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c,
      ToAliasReferenceT d, ToAliasReferenceT e, ToAliasReferenceT f,
      ToAliasReferenceT g, ToAliasReferenceT h)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ident
-> ((a, b), (c, d), (e, f), (g, h))
-> SqlQuery (ToAliasReferenceT ((a, b), (c, d), (e, f), (g, h)))
forall a.
ToAliasReference a =>
Ident -> a -> SqlQuery (ToAliasReferenceT a)
toAliasReference Ident
ident (((a, b), (c, d), (e, f), (g, h))
 -> SqlQuery (ToAliasReferenceT ((a, b), (c, d), (e, f), (g, h))))
-> ((a, b), (c, d), (e, f), (g, h))
-> SqlQuery (ToAliasReferenceT ((a, b), (c, d), (e, f), (g, h)))
forall a b. (a -> b) -> a -> b
$ (a, b, c, d, e, f, g, h) -> ((a, b), (c, d), (e, f), (g, h))
forall a b c d e f g h.
(a, b, c, d, e, f, g, h) -> ((a, b), (c, d), (e, f), (g, h))
from8 (a, b, c, d, e, f, g, h)
x)