From ea4ff33b9308360e10f450963bb1b15a4fbb1bec Mon Sep 17 00:00:00 2001 From: Ben Levy Date: Wed, 26 May 2021 13:12:11 -0500 Subject: [PATCH] Destroy all GADTs; Removes the From GADT and SqlExpr GADT (#228) * Explode the From GADT. Move runFrom into the ToFrom typeclass removing the need for the intermediate structure. Extract the parts of the Experimental module into submodules. * Reorganize Experimental folder. Move Subquery into core Experimental.From module. * Cleanup hackage documentation. Make sure stylish ran correctly. Update changelog and bump version * Update ERaw to change the direction of NeedParens (parent now tells child context). Removed need for composite key constructor * Get rid of AliasedValue and ValueReference; added sqlExprMetaAlias to SqlExprMeta * Remove EList and EEmptyList; ERaw is now technically possible in each case since it is generalized to all * Remove entity specific constructors from SqlExpr * Remove EOrderBy, EDistinctOn; Change PreprocessedFrom a to just be an independent datatype * Remove EOrderByRandom, calling distinctOnOrderBy with rand will choke the db but you shouldnt be using rand anyway. distinctOnOrderBy seems dangerous though * Remove ESet * Remove EInsert and EInsertFinal * Make postgres tests pass * Change aliased val to be legal value by waiting until expr materialization in select clause before adding AS * Cleanup ToAliasRefernce; Add isReference meta to value reference even though that info isnt currently used anywhere * Expose Experimental submodules * Update changelog * Create a FromRaw to replace FromSubquery and FromIdent in from clause. Modify Experimental to only use FromRaw. * Convert all of experimental to use new From type instead of From type class. Make the data constructors second class, functions should be used. Introduce *Lateral functions, using the same type for lateral and non lateral queries was probably a mistake. * Expose the new functions and fix the mysql test compilation error (type inference was wonky with `Union` replaced with `union_` * Bump version and add more comments * ValidOnClause was too restrictive, ToFrom is actually the correct amount of leniency. ValidOnClause would not catch use of on for a cross join but would prevent nested joins * Unbreak lateral joins by introducing a completely different ValidOnClause constraint * Fixe error introduced in merge with master * Dont realias alias references * Never realias an already aliased Entity or Value * reindex value references to the latest 'source' --- changelog.md | 12 + esqueleto.cabal | 11 +- src/Database/Esqueleto.hs | 7 +- src/Database/Esqueleto/Experimental.hs | 975 +----------------- src/Database/Esqueleto/Experimental/From.hs | 147 +++ .../From/CommonTableExpression.hs | 111 ++ .../Esqueleto/Experimental/From/Join.hs | 407 ++++++++ .../Experimental/From/SqlSetOperation.hs | 131 +++ .../Esqueleto/Experimental/ToAlias.hs | 92 ++ .../Experimental/ToAliasReference.hs | 90 ++ .../Esqueleto/Experimental/ToMaybe.hs | 79 ++ src/Database/Esqueleto/Internal/Internal.hs | 830 ++++++--------- src/Database/Esqueleto/Internal/Sql.hs | 2 +- src/Database/Esqueleto/PostgreSQL.hs | 30 +- stack-8.10.yaml | 1 - test/Common/Test.hs | 62 +- test/MySQL/Test.hs | 3 +- test/SQLite/Test.hs | 21 +- 18 files changed, 1514 insertions(+), 1497 deletions(-) create mode 100644 src/Database/Esqueleto/Experimental/From.hs create mode 100644 src/Database/Esqueleto/Experimental/From/CommonTableExpression.hs create mode 100644 src/Database/Esqueleto/Experimental/From/Join.hs create mode 100644 src/Database/Esqueleto/Experimental/From/SqlSetOperation.hs create mode 100644 src/Database/Esqueleto/Experimental/ToAlias.hs create mode 100644 src/Database/Esqueleto/Experimental/ToAliasReference.hs create mode 100644 src/Database/Esqueleto/Experimental/ToMaybe.hs diff --git a/changelog.md b/changelog.md index b9a7acc..577cf0e 100644 --- a/changelog.md +++ b/changelog.md @@ -1,3 +1,14 @@ +3.5.0.0 +======= +- @belevy + - [#228](https://github.com/bitemyapp/esqueleto/pull/228) + - Destroy all GADTs; Removes the From GADT and SqlExpr GADT + - From GADT is replaced with a From data type and FromRaw + - SqlExpr is now all defined in terms of ERaw + - Modified ERaw to contain a SqlExprMeta with any extra information + that may be needed + - Experimental top level is now strictly for documentation and all the + implementation details are in Experimental.* modules 3.4.2.2 ======= - @parsonsmatt @@ -31,6 +42,7 @@ - [#232](https://github.com/bitemyapp/esqueleto/pull/232) - Export the `ValidOnClauseValue` type family + 3.4.0.1 ======= - @arthurxavierx diff --git a/esqueleto.cabal b/esqueleto.cabal index db61f80..6338dfd 100644 --- a/esqueleto.cabal +++ b/esqueleto.cabal @@ -1,7 +1,7 @@ cabal-version: 1.12 name: esqueleto -version: 3.4.2.2 +version: 3.5.0.0 synopsis: Type-safe EDSL for SQL queries on persistent backends. description: @esqueleto@ is a bare bones, type-safe EDSL for SQL queries that works with unmodified @persistent@ SQL backends. Its language closely resembles SQL, so you don't have to learn new concepts, just new syntax, and it's fairly easy to predict the generated SQL and optimize it for your backend. Most kinds of errors committed when writing SQL are caught as compile-time errors---although it is possible to write type-checked @esqueleto@ queries that fail at runtime. . @@ -38,9 +38,16 @@ library Database.Esqueleto.PostgreSQL Database.Esqueleto.PostgreSQL.JSON Database.Esqueleto.SQLite + Database.Esqueleto.Experimental.From + Database.Esqueleto.Experimental.From.CommonTableExpression + Database.Esqueleto.Experimental.From.Join + Database.Esqueleto.Experimental.From.SqlSetOperation + Database.Esqueleto.Experimental.ToAlias + Database.Esqueleto.Experimental.ToAliasReference + Database.Esqueleto.Experimental.ToMaybe other-modules: - Database.Esqueleto.Internal.PersistentImport Database.Esqueleto.PostgreSQL.JSON.Instances + Database.Esqueleto.Internal.PersistentImport Paths_esqueleto hs-source-dirs: src/ diff --git a/src/Database/Esqueleto.hs b/src/Database/Esqueleto.hs index cd92302..2b7a50d 100644 --- a/src/Database/Esqueleto.hs +++ b/src/Database/Esqueleto.hs @@ -1,4 +1,7 @@ -{-# LANGUAGE FlexibleContexts, FlexibleInstances, GADTs, RankNTypes #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE RankNTypes #-} -- | The @esqueleto@ EDSL (embedded domain specific language). -- This module replaces @Database.Persist@, so instead of -- importing that module you should just import this one: @@ -125,8 +128,8 @@ import Control.Monad.Trans.Reader (ReaderT) import Data.Int (Int64) import qualified Data.Map.Strict as Map import Database.Esqueleto.Internal.Language -import Database.Esqueleto.Internal.Sql import Database.Esqueleto.Internal.PersistentImport +import Database.Esqueleto.Internal.Sql import qualified Database.Persist diff --git a/src/Database/Esqueleto/Experimental.hs b/src/Database/Esqueleto/Experimental.hs index 6f707f8..b3c575b 100644 --- a/src/Database/Esqueleto/Experimental.hs +++ b/src/Database/Esqueleto/Experimental.hs @@ -1,15 +1,4 @@ -{-# LANGUAGE CPP #-} -{-# LANGUAGE DataKinds #-} -{-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE FunctionalDependencies #-} -{-# LANGUAGE GADTs #-} -{-# LANGUAGE MultiParamTypeClasses #-} -{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternSynonyms #-} -{-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE TypeOperators #-} -{-# LANGUAGE UndecidableInstances #-} -- | 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, @@ -29,10 +18,24 @@ module Database.Esqueleto.Experimental -- * Documentation - From(..) - , on - , from + -- ** Basic Queries + from + , table + , Table(..) + , SubQuery(..) + , selectQuery + + -- ** Joins , (:&)(..) + , on + , innerJoin + , innerJoinLateral + , leftJoin + , leftJoinLateral + , rightJoin + , fullOuterJoin + , crossJoin + , crossJoinLateral -- ** Set Operations -- $sql-set-operations @@ -50,16 +53,16 @@ module Database.Esqueleto.Experimental , with , withRecursive - -- * Internals - , ToFrom(..) + -- ** Internals + , From(..) , ToMaybe(..) , ToAlias(..) , ToAliasT , ToAliasReference(..) , ToAliasReferenceT - , ValidOnClauseValue - -- * The Normal Stuff + , ToSqlSetOperation(..) + -- * The Normal Stuff , where_ , groupBy , orderBy @@ -172,6 +175,7 @@ module Database.Esqueleto.Experimental , DistinctOn , LockingKind(..) , SqlString + -- ** Joins , InnerJoin(..) , CrossJoin(..) @@ -180,7 +184,8 @@ module Database.Esqueleto.Experimental , FullOuterJoin(..) , JoinKind(..) , OnClauseWithoutMatchingJoinException(..) - -- * SQL backend + + -- ** SQL backend , SqlQuery , SqlExpr , SqlEntity @@ -194,38 +199,36 @@ module Database.Esqueleto.Experimental , insertSelectCount , (<#) , (<&>) + -- ** Rendering Queries , renderQueryToText , renderQuerySelect , renderQueryUpdate , renderQueryDelete , renderQueryInsertInto - -- * Internal.Language - -- * RDBMS-specific modules - -- $rdbmsSpecificModules - -- * Helpers + -- ** Helpers , valkey , valJ , associateJoin - -- * Re-exports + -- ** Re-exports -- $reexports , deleteKey , module Database.Esqueleto.Internal.PersistentImport ) where -import Control.Monad.Trans.Class (lift) -import qualified Control.Monad.Trans.State as S -import qualified Control.Monad.Trans.Writer as W -#if __GLASGOW_HASKELL__ < 804 -import Data.Semigroup -#endif -import Data.Kind (Constraint) -import Data.Proxy (Proxy(..)) -import qualified Data.Text.Lazy.Builder as TLB import Database.Esqueleto.Internal.Internal hiding (From, from, on) import Database.Esqueleto.Internal.PersistentImport + +import Database.Esqueleto.Experimental.From +import Database.Esqueleto.Experimental.From.CommonTableExpression +import Database.Esqueleto.Experimental.From.Join +import Database.Esqueleto.Experimental.From.SqlSetOperation +import Database.Esqueleto.Experimental.ToAlias +import Database.Esqueleto.Experimental.ToAliasReference +import Database.Esqueleto.Experimental.ToMaybe + import GHC.TypeLits import Database.Persist (EntityNameDB(..)) @@ -317,7 +320,7 @@ import Database.Persist (EntityNameDB(..)) -- -- @ -- select $ do --- people <- from $ Table \@Person +-- people <- from $ table \@Person -- where_ (people ^. PersonName ==. val \"John\") -- pure people -- @ @@ -345,8 +348,8 @@ import Database.Persist (EntityNameDB(..)) -- @ -- select $ do -- (people :& blogPosts) <- --- from $ Table \@Person --- \`LeftOuterJoin\` Table \@BlogPost +-- from $ table \@Person +-- \`leftJoin\` table \@BlogPost -- \`on\` (\\(people :& blogPosts) -> -- people ^. PersonId ==. blogPosts ?. BlogPostAuthorId) -- where_ (people ^. PersonAge >. val 18) @@ -377,7 +380,7 @@ import Database.Persist (EntityNameDB(..)) -- -- 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 +-- 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. @@ -385,11 +388,11 @@ import Database.Persist (EntityNameDB(..)) -- @ -- select $ do -- (people1 :& followers :& people2) <- --- from $ Table \@Person --- \`InnerJoin` Table \@Follow +-- from $ table \@Person +-- \`innerJoin` table \@Follow -- \`on\` (\\(people1 :& followers) -> -- people1 ^. PersonId ==. followers ^. FollowFollowed) --- \`InnerJoin` Table \@Person +-- \`innerJoin` table \@Person -- \`on\` (\\(_ :& followers :& people2) -> -- followers ^. FollowFollower ==. people2 ^. PersonId) -- where_ (people1 ^. PersonName ==. val \"John\") @@ -421,8 +424,8 @@ import Database.Persist (EntityNameDB(..)) -- peopleWithPosts <- -- from $ do -- (people :& blogPosts) <- --- from $ Table \@Person --- \`InnerJoin\` Table \@BlogPost +-- from $ table \@Person +-- \`innerJoin\` table \@BlogPost -- \`on\` (\\(p :& bP) -> -- p ^. PersonId ==. bP ^. BlogPostAuthorId) -- groupBy (people ^. PersonId) @@ -452,8 +455,8 @@ import Database.Persist (EntityNameDB(..)) -- (authors, blogPosts) <- from $ -- (do -- (author :& blogPost) <- --- from $ Table \@Person --- \`InnerJoin\` Table \@BlogPost +-- from $ table \@Person +-- \`innerJoin\` table \@BlogPost -- \`on\` (\\(a :& bP) -> -- a ^. PersonId ==. bP ^. BlogPostAuthorId) -- where_ (author ^. PersonId ==. val currentPersonId) @@ -462,11 +465,11 @@ import Database.Persist (EntityNameDB(..)) -- \`union_\` -- (do -- (follow :& blogPost :& author) <- --- from $ Table \@Follow --- \`InnerJoin\` Table \@BlogPost +-- from $ table \@Follow +-- \`innerJoin\` table \@BlogPost -- \`on\` (\\(f :& bP) -> -- f ^. FollowFollowed ==. bP ^. BlogPostAuthorId) --- \`InnerJoin\` Table \@Person +-- \`innerJoin\` table \@Person -- \`on\` (\\(_ :& bP :& a) -> -- bP ^. BlogPostAuthorId ==. a ^. PersonId) -- where_ (follow ^. FollowFollower ==. val currentPersonId) @@ -485,14 +488,14 @@ import Database.Persist (EntityNameDB(..)) -- @ -- select $ do -- (salesPerson :& maxSaleAmount :& maxSaleCustomerName) <- --- from $ Table \@SalesPerson --- \`CrossJoin\` (\\salesPerson -> do --- sales <- from $ Table \@Sale +-- from $ table \@SalesPerson +-- \`crossJoinLateral\` (\\salesPerson -> do +-- sales <- from $ table \@Sale -- where_ $ sales ^. SaleSalesPersonId ==. salesPerson ^. SalesPersonId -- pure $ max_ (sales ^. SaleAmount) -- ) --- \`CrossJoin\` (\\(salesPerson :& maxSaleAmount) -> do --- sales <- from $ Table \@Sale +-- \`crossJoinLateral\` (\\(salesPerson :& maxSaleAmount) -> do +-- sales <- from $ table \@Sale -- where_ $ sales ^. SaleSalesPersonId ==. salesPerson ^. SalesPersonId -- &&. sales ^. SaleAmount ==. maxSaleAmount -- pure $ sales ^. SaleCustomerName) @@ -527,27 +530,6 @@ import Database.Persist (EntityNameDB(..)) -- AS max_sale_customer; -- @ --- | 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 SqlSetOperation a - = SqlSetUnion (SqlSetOperation a) (SqlSetOperation a) - | SqlSetUnionAll (SqlSetOperation a) (SqlSetOperation a) - | SqlSetExcept (SqlSetOperation a) (SqlSetOperation a) - | SqlSetIntersect (SqlSetOperation a) (SqlSetOperation a) - | SelectQueryP NeedParens (SqlQuery a) - -- $sql-set-operations -- -- Data type that represents SQL set operations. This includes @@ -561,12 +543,12 @@ data SqlSetOperation a -- @ -- select $ from $ -- (do --- a <- from Table @A +-- a <- from $ table @A -- pure $ a ^. ASomeCol -- ) -- \`union_\` -- (do --- b <- from Table @B +-- b <- from $ table @B -- pure $ b ^. BSomeCol -- ) -- @ @@ -581,846 +563,3 @@ data SqlSetOperation a -- ) -- @ -- - -{-# DEPRECATED Union "/Since: 3.4.0.0/ - Use the 'union_' function instead of the 'Union' data constructor" #-} -data Union a b = a `Union` b - --- | @UNION@ SQL set operation. Can be used as an infix function between 'SqlQuery' values. -union_ :: a -> b -> Union a b -union_ = Union - -{-# DEPRECATED UnionAll "/Since: 3.4.0.0/ - Use the 'unionAll_' function instead of the 'UnionAll' data constructor" #-} -data UnionAll a b = a `UnionAll` b - --- | @UNION@ @ALL@ SQL set operation. Can be used as an infix function between 'SqlQuery' values. -unionAll_ :: a -> b -> UnionAll a b -unionAll_ = UnionAll - -{-# DEPRECATED Except "/Since: 3.4.0.0/ - Use the 'except_' function instead of the 'Except' data constructor" #-} -data Except a b = a `Except` b - --- | @EXCEPT@ SQL set operation. Can be used as an infix function between 'SqlQuery' values. -except_ :: a -> b -> Except a b -except_ = Except - -{-# DEPRECATED Intersect "/Since: 3.4.0.0/ - Use the 'intersect_' function instead of the 'Intersect' data constructor" #-} -data Intersect a b = a `Intersect` b - --- | @INTERSECT@ SQL set operation. Can be used as an infix function between 'SqlQuery' values. -intersect_ :: a -> b -> Intersect a b -intersect_ = Intersect - -class SetOperationT a ~ b => ToSetOperation a b | a -> b where - type SetOperationT a - toSetOperation :: a -> SqlSetOperation b -instance ToSetOperation (SqlSetOperation a) a where - type SetOperationT (SqlSetOperation a) = a - toSetOperation = id -instance ToSetOperation (SqlQuery a) a where - type SetOperationT (SqlQuery a) = a - toSetOperation = SelectQueryP Never -instance (ToSetOperation a c, ToSetOperation b c) => ToSetOperation (Union a b) c where - type SetOperationT (Union a b) = SetOperationT a - toSetOperation (Union a b) = SqlSetUnion (toSetOperation a) (toSetOperation b) -instance (ToSetOperation a c, ToSetOperation b c) => ToSetOperation (UnionAll a b) c where - type SetOperationT (UnionAll a b) = SetOperationT a - toSetOperation (UnionAll a b) = SqlSetUnionAll (toSetOperation a) (toSetOperation b) -instance (ToSetOperation a c, ToSetOperation b c) => ToSetOperation (Except a b) c where - type SetOperationT (Except a b) = SetOperationT a - toSetOperation (Except a b) = SqlSetExcept (toSetOperation a) (toSetOperation b) -instance (ToSetOperation a c, ToSetOperation b c) => ToSetOperation (Intersect a b) c where - type SetOperationT (Intersect a b) = SetOperationT a - toSetOperation (Intersect a b) = SqlSetIntersect (toSetOperation a) (toSetOperation b) - -{-# DEPRECATED SelectQuery "/Since: 3.4.0.0/ - It is no longer necessary to tag 'SqlQuery' values with @SelectQuery@" #-} -pattern SelectQuery :: SqlQuery a -> SqlSetOperation a -pattern 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 - , ToAlias a - , ToAliasReference a - ) - => SqlQuery a - -> From a - FromCte - :: Ident - -> a - -> From a - SqlSetOperation - :: ( SqlSelect a r - , ToAlias a - , ToAliasReference a - ) - => SqlSetOperation a - -> From a - InnerJoinFrom - :: From a - -> (From b, (a :& b) -> SqlExpr (Value Bool)) - -> From (a :& b) - InnerJoinFromLateral - :: ( SqlSelect b r - , ToAlias b - , ToAliasReference b - ) - => From a - -> ((a -> SqlQuery b), (a :& b) -> SqlExpr (Value Bool)) - -> From (a :& b) - CrossJoinFrom - :: From a - -> From b - -> From (a :& b) - CrossJoinFromLateral - :: ( SqlSelect b r - , ToAlias b - , ToAliasReference b - ) - => From a - -> (a -> SqlQuery b) - -> From (a :& b) - LeftJoinFrom - :: ToMaybe b - => From a - -> (From b, (a :& ToMaybeT b) -> SqlExpr (Value Bool)) - -> From (a :& ToMaybeT b) - LeftJoinFromLateral - :: ( SqlSelect b r - , ToAlias b - , ToAliasReference b - , ToMaybe b - ) - => From a - -> ((a -> SqlQuery 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) - --- | Constraint for `on`. Ensures that only types that require an `on` can be used on --- the left hand side. This was previously reusing the ToFrom class which was actually --- a bit too lenient as it allowed to much. --- --- @since 3.4.0.0 -type family ValidOnClauseValue a :: Constraint where - ValidOnClauseValue (From a) = () - ValidOnClauseValue (SqlQuery a) = () - ValidOnClauseValue (SqlSetOperation a) = () - ValidOnClauseValue (a -> SqlQuery b) = () - ValidOnClauseValue _ = TypeError ('Text "Illegal use of ON") - --- | 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 :: ValidOnClauseValue a => a -> (b -> SqlExpr (Value Bool)) -> (a, b -> SqlExpr (Value Bool)) -on = (,) -infix 9 `on` - -data Lateral -data NotLateral - -type family IsLateral a where - IsLateral (a -> SqlQuery b) = Lateral - IsLateral a = NotLateral - -type family ErrorOnLateral a :: Constraint where - ErrorOnLateral (a -> SqlQuery b) = TypeError ('Text "LATERAL can only be used for INNER, LEFT, and CROSS join kinds.") - ErrorOnLateral _ = () - -{-- Type class magic to allow the use of the `InnerJoin` family of data constructors in from --} -class ToFrom a where - type ToFromT a - toFrom :: a -> From (ToFromT a) - --- @since 3.4.0.1 -type family FromOnClause a where - FromOnClause (a, b -> SqlExpr (Value Bool)) = b - FromOnClause a = TypeError ('Text "Missing ON clause") - -instance {-# OVERLAPPABLE #-} ToFrom (InnerJoin a b) where - type ToFromT (InnerJoin a b) = FromOnClause b - toFrom = undefined -instance {-# OVERLAPPABLE #-} ToFrom (LeftOuterJoin a b) where - type ToFromT (LeftOuterJoin a b) = FromOnClause b - toFrom = undefined -instance {-# OVERLAPPABLE #-} ToFrom (FullOuterJoin a b) where - type ToFromT (FullOuterJoin a b) = FromOnClause b - toFrom = undefined -instance {-# OVERLAPPABLE #-} ToFrom (RightOuterJoin a b) where - type ToFromT (RightOuterJoin a b) = FromOnClause b - toFrom = undefined - -instance ToFrom (From a) where - type ToFromT (From a) = a - toFrom = id - -instance - ( ToAlias a - , ToAliasReference a - , SqlSelect a r - ) - => - ToFrom (SqlQuery a) - where - type ToFromT (SqlQuery a) = a - toFrom = SubQuery - -instance - ( SqlSelect c r - , ToAlias c - , ToAliasReference c - , ToSetOperation a c - , ToSetOperation b c - , c ~ SetOperationT a - ) - => - ToFrom (Union a b) - where - type ToFromT (Union a b) = SetOperationT a - toFrom u = SqlSetOperation $ toSetOperation u - -instance - ( SqlSelect c r - , ToAlias c - , ToAliasReference c - , ToSetOperation a c - , ToSetOperation b c - , c ~ SetOperationT a - ) - => - ToFrom (UnionAll a b) - where - type ToFromT (UnionAll a b) = SetOperationT a - toFrom u = SqlSetOperation $ toSetOperation u - -instance - ( SqlSelect c r - , ToAlias c - , ToAliasReference c - , ToSetOperation a c - , ToSetOperation b c - , c ~ SetOperationT a - ) - => - ToFrom (Intersect a b) - where - type ToFromT (Intersect a b) = SetOperationT a - toFrom u = SqlSetOperation $ toSetOperation u - -instance - ( SqlSelect c r - , ToAlias c - , ToAliasReference c - , ToSetOperation a c - , ToSetOperation b c - , c ~ SetOperationT a - ) - => - ToFrom (Except a b) - where - type ToFromT (Except a b) = SetOperationT a - toFrom u = SqlSetOperation $ toSetOperation u - -instance (SqlSelect a r, ToAlias a, ToAliasReference a) => ToFrom (SqlSetOperation a) where - type ToFromT (SqlSetOperation a) = a - -- If someone uses just a plain SelectQuery it should behave like a normal subquery - toFrom (SelectQueryP _ q) = SubQuery q - -- Otherwise use the SqlSetOperation - toFrom q = SqlSetOperation q - -class ToInnerJoin lateral lhs rhs res where - toInnerJoin :: Proxy lateral -> lhs -> rhs -> (res -> SqlExpr (Value Bool)) -> From res - -instance ( SqlSelect b r - , ToAlias b - , ToAliasReference b - , ToFrom a - , ToFromT a ~ a' - ) => ToInnerJoin Lateral a (a' -> SqlQuery b) (a' :& b) where - toInnerJoin _ lhs q on' = InnerJoinFromLateral (toFrom lhs) (q, on') - -instance (ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b') - => ToInnerJoin NotLateral a b (a' :& b') where - toInnerJoin _ lhs rhs on' = InnerJoinFrom (toFrom lhs) (toFrom rhs, on') - -instance (ToInnerJoin (IsLateral b) a b b') => ToFrom (InnerJoin a (b, b' -> SqlExpr (Value Bool))) where - type ToFromT (InnerJoin a (b, b' -> SqlExpr (Value Bool))) = FromOnClause (b, b' -> SqlExpr(Value Bool)) - toFrom (InnerJoin lhs (rhs, on')) = toInnerJoin (toProxy rhs) lhs rhs on' - where - toProxy :: b -> Proxy (IsLateral b) - toProxy _ = Proxy - --- @since 3.4.0.1 -type family FromCrossJoin a b where - FromCrossJoin a (b -> SqlQuery c) = ToFromT a :& c - FromCrossJoin a b = ToFromT a :& ToFromT b - -instance ( ToFrom a - , ToFrom b - , ToFromT (CrossJoin a b) ~ (ToFromT a :& ToFromT b) - ) => ToFrom (CrossJoin a b) where - type ToFromT (CrossJoin a b) = FromCrossJoin a b - toFrom (CrossJoin lhs rhs) = CrossJoinFrom (toFrom lhs) (toFrom rhs) - -instance {-# OVERLAPPING #-} - ( ToFrom a - , ToFromT a ~ a' - , SqlSelect b r - , ToAlias b - , ToAliasReference b - ) => ToFrom (CrossJoin a (a' -> SqlQuery b)) where - type ToFromT (CrossJoin a (a' -> SqlQuery b)) = FromCrossJoin a (a' -> SqlQuery b) - toFrom (CrossJoin lhs q) = CrossJoinFromLateral (toFrom lhs) q - -class ToLeftJoin lateral lhs rhs res where - toLeftJoin :: Proxy lateral -> lhs -> rhs -> (res -> SqlExpr (Value Bool)) -> From res - -instance ( ToFrom a - , ToFromT a ~ a' - , SqlSelect b r - , ToAlias b - , ToAliasReference b - , ToMaybe b - , mb ~ ToMaybeT b - ) => ToLeftJoin Lateral a (a' -> SqlQuery b) (a' :& mb) where - toLeftJoin _ lhs q on' = LeftJoinFromLateral (toFrom lhs) (q, on') - -instance ( ToFrom a - , ToFromT a ~ a' - , ToFrom b - , ToFromT b ~ b' - , ToMaybe b' - , mb ~ ToMaybeT b' - ) => ToLeftJoin NotLateral a b (a' :& mb) where - toLeftJoin _ lhs rhs on' = LeftJoinFrom (toFrom lhs) (toFrom rhs, on') - -instance ( ToLeftJoin (IsLateral b) a b b' - ) => ToFrom (LeftOuterJoin a (b, b' -> SqlExpr (Value Bool))) where - type ToFromT (LeftOuterJoin a (b, b' -> SqlExpr (Value Bool))) = FromOnClause (b, b' -> SqlExpr(Value Bool)) - toFrom (LeftOuterJoin lhs (rhs, on')) = - toLeftJoin (toProxy rhs) lhs rhs on' - where - toProxy :: b -> Proxy (IsLateral b) - toProxy _ = Proxy - -instance ( ToFrom a - , ToFromT a ~ a' - , ToFrom b - , ToFromT b ~ b' - , ToMaybe a' - , ma ~ ToMaybeT a' - , ToMaybe b' - , mb ~ ToMaybeT b' - , ErrorOnLateral b - ) => ToFrom (FullOuterJoin a (b, (ma :& mb) -> SqlExpr (Value Bool))) where - type ToFromT (FullOuterJoin a (b, (ma :& mb) -> SqlExpr (Value Bool))) = FromOnClause (b, (ma :& mb) -> SqlExpr(Value Bool)) - toFrom (FullOuterJoin lhs (rhs, on')) = FullJoinFrom (toFrom lhs) (toFrom rhs, on') - -instance ( ToFrom a - , ToFromT a ~ a' - , ToMaybe a' - , ma ~ ToMaybeT a' - , ToFrom b - , ToFromT b ~ b' - , ErrorOnLateral b - ) => ToFrom (RightOuterJoin a (b, (ma :& b') -> SqlExpr (Value Bool))) where - type ToFromT (RightOuterJoin a (b, (ma :& b') -> SqlExpr (Value Bool))) = FromOnClause (b, (ma :& b') -> SqlExpr(Value Bool)) - toFrom (RightOuterJoin lhs (rhs, on')) = RightJoinFrom (toFrom lhs) (toFrom rhs, on') - -type family Nullable a where - Nullable (Maybe a) = a - Nullable a = a - -class ToMaybe a where - type ToMaybeT a - toMaybe :: a -> ToMaybeT a - -instance ToMaybe (SqlExpr (Maybe a)) where - type ToMaybeT (SqlExpr (Maybe a)) = SqlExpr (Maybe a) - toMaybe = id - -instance ToMaybe (SqlExpr (Entity a)) where - type ToMaybeT (SqlExpr (Entity a)) = SqlExpr (Maybe (Entity a)) - toMaybe = EMaybe - -instance ToMaybe (SqlExpr (Value a)) where - type ToMaybeT (SqlExpr (Value a)) = SqlExpr (Value (Maybe (Nullable a))) - toMaybe = veryUnsafeCoerceSqlExprValue - -instance (ToMaybe a, ToMaybe b) => ToMaybe (a :& b) where - type ToMaybeT (a :& b) = (ToMaybeT a :& ToMaybeT b) - toMaybe (a :& b) = (toMaybe a :& toMaybe b) - -instance (ToMaybe a, ToMaybe b) => ToMaybe (a,b) where - type ToMaybeT (a, b) = (ToMaybeT a, ToMaybeT b) - toMaybe (a, b) = (toMaybe a, toMaybe b) - -instance ( ToMaybe a , ToMaybe b , ToMaybe c) => ToMaybe (a,b,c) where - type ToMaybeT (a, b, c) = (ToMaybeT a, ToMaybeT b, ToMaybeT c) - toMaybe = to3 . toMaybe . from3 - -instance ( ToMaybe a , ToMaybe b , ToMaybe c , ToMaybe d) => ToMaybe (a,b,c,d) where - type ToMaybeT (a, b, c, d) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d) - toMaybe = to4 . toMaybe . from4 - -instance ( ToMaybe a , ToMaybe b , ToMaybe c , ToMaybe d , ToMaybe e) => ToMaybe (a,b,c,d,e) where - type ToMaybeT (a, b, c, d, e) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e) - toMaybe = to5 . toMaybe . from5 - -instance ( ToMaybe a - , ToMaybe b - , ToMaybe c - , ToMaybe d - , ToMaybe e - , ToMaybe f - ) => ToMaybe (a,b,c,d,e,f) where - type ToMaybeT (a, b, c, d, e, f) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e, ToMaybeT f) - toMaybe = to6 . toMaybe . 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 - type ToMaybeT (a, b, c, d, e, f, g) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e, ToMaybeT f, ToMaybeT g) - toMaybe = to7 . toMaybe . 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 - type 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) - toMaybe = to8 . toMaybe . 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 parts = do - (a, clause) <- runFrom $ toFrom parts - Q $ W.tell mempty{sdFromClause=[clause]} - pure a - where - runFrom :: From a -> SqlQuery (a, FromClause) - runFrom e@Table = do - let ed = entityDef $ getVal e - ident <- newIdentFor . DBName . unEntityNameDB $ getEntityDBName ed - let entity = EEntity ident - pure $ (entity, FromStart ident ed) - where - getVal :: From (SqlExpr (Entity ent)) -> Proxy ent - getVal = const Proxy - runFrom (SubQuery subquery) = - fromSubQuery NormalSubQuery subquery - - runFrom (FromCte ident ref) = - pure (ref, FromIdent ident) - - runFrom (SqlSetOperation operation) = do - (aliasedOperation, ret) <- aliasQueries operation - ident <- newIdentFor (DBName "u") - ref <- toAliasReference ident ret - pure (ref, FromQuery ident (operationToSql aliasedOperation) NormalSubQuery) - - where - aliasQueries o = - case o of - SelectQueryP p q -> do - (ret, sideData) <- Q $ W.censor (\_ -> mempty) $ W.listen $ unQ q - prevState <- Q $ lift S.get - aliasedRet <- toAlias ret - Q $ lift $ S.put prevState - let p' = - case p of - Parens -> Parens - Never -> - if (sdLimitClause sideData) /= mempty - || length (sdOrderByClause sideData) > 0 then - Parens - else - Never - pure (SelectQueryP p' $ Q $ W.WriterT $ pure (aliasedRet, sideData), aliasedRet) - SqlSetUnion o1 o2 -> do - (o1', ret) <- aliasQueries o1 - (o2', _ ) <- aliasQueries o2 - pure (SqlSetUnion o1' o2', ret) - SqlSetUnionAll o1 o2 -> do - (o1', ret) <- aliasQueries o1 - (o2', _ ) <- aliasQueries o2 - pure (SqlSetUnionAll o1' o2', ret) - SqlSetExcept o1 o2 -> do - (o1', ret) <- aliasQueries o1 - (o2', _ ) <- aliasQueries o2 - pure (SqlSetExcept o1' o2', ret) - SqlSetIntersect o1 o2 -> do - (o1', ret) <- aliasQueries o1 - (o2', _ ) <- aliasQueries o2 - pure (SqlSetIntersect o1' o2', ret) - - operationToSql o info = - case o of - SelectQueryP p q -> - let (builder, values) = toRawSql SELECT info q - in (parensM p builder, values) - SqlSetUnion o1 o2 -> doSetOperation "UNION" info o1 o2 - SqlSetUnionAll o1 o2 -> doSetOperation "UNION ALL" info o1 o2 - SqlSetExcept o1 o2 -> doSetOperation "EXCEPT" info o1 o2 - SqlSetIntersect o1 o2 -> doSetOperation "INTERSECT" info o1 o2 - - doSetOperation operationText info o1 o2 = - let (q1, v1) = operationToSql o1 info - (q2, v2) = operationToSql o2 info - in (q1 <> " " <> operationText <> " " <> q2, v1 <> v2) - - runFrom (InnerJoinFrom leftPart (rightPart, on')) = do - (leftVal, leftFrom) <- runFrom leftPart - (rightVal, rightFrom) <- runFrom rightPart - let ret = leftVal :& rightVal - pure $ (ret, FromJoin leftFrom InnerJoinKind rightFrom (Just (on' ret))) - runFrom (InnerJoinFromLateral leftPart (q, on')) = do - (leftVal, leftFrom) <- runFrom leftPart - (rightVal, rightFrom) <- fromSubQuery LateralSubQuery (q leftVal) - let ret = leftVal :& rightVal - pure $ (ret, FromJoin leftFrom InnerJoinKind rightFrom (Just (on' ret))) - runFrom (CrossJoinFrom leftPart rightPart) = do - (leftVal, leftFrom) <- runFrom leftPart - (rightVal, rightFrom) <- runFrom rightPart - let ret = leftVal :& rightVal - pure $ (ret, FromJoin leftFrom CrossJoinKind rightFrom Nothing) - runFrom (CrossJoinFromLateral leftPart q) = do - (leftVal, leftFrom) <- runFrom leftPart - (rightVal, rightFrom) <- fromSubQuery LateralSubQuery (q leftVal) - let ret = leftVal :& rightVal - pure $ (ret, FromJoin leftFrom CrossJoinKind rightFrom Nothing) - runFrom (LeftJoinFrom leftPart (rightPart, on')) = do - (leftVal, leftFrom) <- runFrom leftPart - (rightVal, rightFrom) <- runFrom rightPart - let ret = leftVal :& (toMaybe rightVal) - pure $ (ret, FromJoin leftFrom LeftOuterJoinKind rightFrom (Just (on' ret))) - runFrom (LeftJoinFromLateral leftPart (q, on')) = do - (leftVal, leftFrom) <- runFrom leftPart - (rightVal, rightFrom) <- fromSubQuery LateralSubQuery (q leftVal) - let ret = leftVal :& (toMaybe rightVal) - pure $ (ret, FromJoin leftFrom LeftOuterJoinKind rightFrom (Just (on' ret))) - runFrom (RightJoinFrom leftPart (rightPart, on')) = do - (leftVal, leftFrom) <- runFrom leftPart - (rightVal, rightFrom) <- runFrom rightPart - let ret = (toMaybe leftVal) :& rightVal - pure $ (ret, FromJoin leftFrom RightOuterJoinKind rightFrom (Just (on' ret))) - runFrom (FullJoinFrom leftPart (rightPart, on')) = do - (leftVal, leftFrom) <- runFrom leftPart - (rightVal, rightFrom) <- runFrom rightPart - let ret = (toMaybe leftVal) :& (toMaybe rightVal) - pure $ (ret, FromJoin leftFrom FullOuterJoinKind rightFrom (Just (on' ret))) - -fromSubQuery - :: - ( SqlSelect a r - , ToAlias a - , ToAliasReference a - ) - => SubQueryType -> SqlQuery a -> SqlQuery (a, FromClause) -fromSubQuery subqueryType subquery = do - -- We want to update the IdentState without writing the query to side data - (ret, sideData) <- Q $ W.censor (\_ -> mempty) $ W.listen $ unQ subquery - aliasedValue <- toAlias ret - -- Make a fake query with the aliased results, this allows us to ensure that the query is only run once - let aliasedQuery = Q $ W.WriterT $ pure (aliasedValue, sideData) - -- Add the FromQuery that renders the subquery to our side data - subqueryAlias <- newIdentFor (DBName "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. - ref <- toAliasReference subqueryAlias aliasedValue - pure (ref , FromQuery subqueryAlias (\info -> toRawSql SELECT info aliasedQuery) subqueryType) - --- | @WITH@ clause used to introduce a [Common Table Expression (CTE)](https://en.wikipedia.org/wiki/Hierarchical_and_recursive_queries_in_SQL#Common_table_expression). --- CTEs are supported in most modern SQL engines and can be useful --- in performance tuning. In Esqueleto, CTEs should be used as a --- subquery memoization tactic. When writing plain SQL, CTEs --- are sometimes used to organize the SQL code, in Esqueleto, this --- is better achieved through function that return 'SqlQuery' values. --- --- @ --- select $ do --- cte <- with subQuery --- cteResult <- from cte --- where_ $ cteResult ... --- pure cteResult --- @ --- --- __WARNING__: In some SQL engines using a CTE can diminish performance. --- In these engines the CTE is treated as an optimization fence. You should --- always verify that using a CTE will in fact improve your performance --- over a regular subquery. --- --- /Since: 3.4.0.0/ -with :: ( ToAlias a - , ToAliasReference a - , SqlSelect a r - ) => SqlQuery a -> SqlQuery (From a) -with query = do - (ret, sideData) <- Q $ W.censor (\_ -> mempty) $ W.listen $ unQ query - aliasedValue <- toAlias ret - let aliasedQuery = Q $ W.WriterT $ pure (aliasedValue, sideData) - ident <- newIdentFor (DBName "cte") - let clause = CommonTableExpressionClause NormalCommonTableExpression ident (\info -> toRawSql SELECT info aliasedQuery) - Q $ W.tell mempty{sdCteClause = [clause]} - ref <- toAliasReference ident aliasedValue - pure $ FromCte ident ref - --- | @WITH@ @RECURSIVE@ allows one to make a recursive subquery, which can --- reference itself. Like @WITH@, this is supported in most modern SQL engines. --- Useful for hierarchical, self-referential data, like a tree of data. --- --- @ --- select $ do --- cte <- withRecursive --- (do $ --- person <- from $ Table \@Person --- where_ $ person ^. PersonId ==. val personId --- pure person --- ) --- unionAll_ --- (\\self -> do $ --- (p :& f :& p2 :& pSelf) <- from self --- \`InnerJoin\` $ Table \@Follow --- \`on\` (\\(p :& f) -> --- p ^. PersonId ==. f ^. FollowFollower) --- \`InnerJoin\` $ Table \@Person --- \`on\` (\\(p :& f :& p2) -> --- f ^. FollowFollowed ==. p2 ^. PersonId) --- \`LeftOuterJoin\` self --- \`on\` (\\(_ :& _ :& p2 :& pSelf) -> --- just (p2 ^. PersonId) ==. pSelf ?. PersonId) --- where_ $ isNothing (pSelf ?. PersonId) --- groupBy (p2 ^. PersonId) --- pure p2 --- ) --- from cte --- @ --- --- /Since: 3.4.0.0/ -withRecursive :: ( ToAlias a - , ToAliasReference a - , SqlSelect a r - , RecursiveCteUnion unionKind - ) - => SqlQuery a - -> unionKind - -> (From a -> SqlQuery a) - -> SqlQuery (From a) -withRecursive baseCase unionKind recursiveCase = do - (ret, sideData) <- Q $ W.censor (\_ -> mempty) $ W.listen $ unQ baseCase - aliasedValue <- toAlias ret - let aliasedQuery = Q $ W.WriterT $ pure (aliasedValue, sideData) - ident <- newIdentFor (DBName "cte") - ref <- toAliasReference ident aliasedValue - let refFrom = FromCte ident ref - let recursiveQuery = recursiveCase refFrom - let clause = CommonTableExpressionClause RecursiveCommonTableExpression ident - (\info -> (toRawSql SELECT info aliasedQuery) - <> (unionKeyword unionKind, mempty) - <> (toRawSql SELECT info recursiveQuery) - ) - Q $ W.tell mempty{sdCteClause = [clause]} - pure refFrom - -{-# DEPRECATED ToAliasT "This type alias doesn't do anything. Please delete it. Will be removed in the next release." #-} -type ToAliasT a = a - --- Tedious tuple magic -class ToAlias a where - toAlias :: a -> SqlQuery a - -instance ToAlias (SqlExpr (Value a)) where - toAlias v@(EAliasedValue _ _) = pure v - toAlias v = do - ident <- newIdentFor (DBName "v") - pure $ EAliasedValue ident v - -instance ToAlias (SqlExpr (Entity a)) where - toAlias v@(EAliasedEntityReference _ _) = pure v - toAlias v@(EAliasedEntity _ _) = pure v - toAlias (EEntity tableIdent) = do - ident <- newIdentFor (DBName "v") - pure $ EAliasedEntity ident tableIdent - -instance ToAlias (SqlExpr (Maybe (Entity a))) where - toAlias (EMaybe e) = EMaybe <$> toAlias e - -instance (ToAlias a, ToAlias b) => ToAlias (a,b) where - toAlias (a,b) = (,) <$> toAlias a <*> toAlias b - -instance ( ToAlias a - , ToAlias b - , ToAlias c - ) => ToAlias (a,b,c) where - toAlias x = to3 <$> (toAlias $ from3 x) - -instance ( ToAlias a - , ToAlias b - , ToAlias c - , ToAlias d - ) => ToAlias (a,b,c,d) where - toAlias x = to4 <$> (toAlias $ from4 x) - -instance ( ToAlias a - , ToAlias b - , ToAlias c - , ToAlias d - , ToAlias e - ) => ToAlias (a,b,c,d,e) where - toAlias x = to5 <$> (toAlias $ from5 x) - -instance ( ToAlias a - , ToAlias b - , ToAlias c - , ToAlias d - , ToAlias e - , ToAlias f - ) => ToAlias (a,b,c,d,e,f) where - toAlias x = to6 <$> (toAlias $ from6 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 x = to7 <$> (toAlias $ from7 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 x = to8 <$> (toAlias $ from8 x) - -{-# DEPRECATED ToAliasReferenceT "This type alias doesn't do anything. Please delete it. Will be removed in the next release." #-} -type ToAliasReferenceT a = a - --- more tedious tuple magic -class ToAliasReference a where - toAliasReference :: Ident -> a -> SqlQuery a - -instance ToAliasReference (SqlExpr (Value a)) where - toAliasReference aliasSource (EAliasedValue aliasIdent _) = pure $ EValueReference aliasSource (\_ -> aliasIdent) - toAliasReference _ v@(ERaw _ _) = toAlias v - toAliasReference _ v@(ECompositeKey _) = toAlias v - toAliasReference s (EValueReference _ b) = pure $ EValueReference s b - -instance ToAliasReference (SqlExpr (Entity a)) where - toAliasReference aliasSource (EAliasedEntity ident _) = pure $ EAliasedEntityReference aliasSource ident - toAliasReference _ e@(EEntity _) = toAlias e - toAliasReference s (EAliasedEntityReference _ b) = pure $ EAliasedEntityReference s b - -instance ToAliasReference (SqlExpr (Maybe (Entity a))) where - toAliasReference s (EMaybe e) = EMaybe <$> toAliasReference s e - - -instance (ToAliasReference a, ToAliasReference b) => ToAliasReference (a, b) where - toAliasReference ident (a,b) = (,) <$> (toAliasReference ident a) <*> (toAliasReference ident b) - -instance ( ToAliasReference a - , ToAliasReference b - , ToAliasReference c - ) => ToAliasReference (a,b,c) where - toAliasReference ident x = fmap to3 $ toAliasReference ident $ from3 x - -instance ( ToAliasReference a - , ToAliasReference b - , ToAliasReference c - , ToAliasReference d - ) => ToAliasReference (a,b,c,d) where - toAliasReference ident x = fmap to4 $ toAliasReference ident $ from4 x - -instance ( ToAliasReference a - , ToAliasReference b - , ToAliasReference c - , ToAliasReference d - , ToAliasReference e - ) => ToAliasReference (a,b,c,d,e) where - toAliasReference ident x = fmap to5 $ toAliasReference ident $ from5 x - -instance ( ToAliasReference a - , ToAliasReference b - , ToAliasReference c - , ToAliasReference d - , ToAliasReference e - , ToAliasReference f - ) => ToAliasReference (a,b,c,d,e,f) where - toAliasReference ident x = to6 <$> (toAliasReference ident $ from6 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 x = to7 <$> (toAliasReference ident $ from7 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 x = to8 <$> (toAliasReference ident $ from8 x) - -class RecursiveCteUnion a where - unionKeyword :: a -> TLB.Builder - -instance RecursiveCteUnion (a -> b -> Union a b) where - unionKeyword _ = "\nUNION\n" - -instance RecursiveCteUnion (a -> b -> UnionAll a b) where - unionKeyword _ = "\nUNION ALL\n" diff --git a/src/Database/Esqueleto/Experimental/From.hs b/src/Database/Esqueleto/Experimental/From.hs new file mode 100644 index 0000000..c170283 --- /dev/null +++ b/src/Database/Esqueleto/Experimental/From.hs @@ -0,0 +1,147 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE FunctionalDependencies #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE UndecidableInstances #-} + +module Database.Esqueleto.Experimental.From + where + +import Control.Arrow (first) +import Control.Monad (ap) +import qualified Control.Monad.Trans.Writer as W +import Data.Coerce (coerce) +import Data.Proxy +import qualified Data.Text.Lazy.Builder as TLB +import Database.Esqueleto.Experimental.ToAlias +import Database.Esqueleto.Experimental.ToAliasReference +import Database.Esqueleto.Internal.Internal hiding (From(..), from, on) +import Database.Esqueleto.Internal.PersistentImport + +import Database.Persist.Names (EntityNameDB(..)) + +-- | 'FROM' clause, used to bring entities into scope. +-- +-- Internally, this function uses the `From` datatype. +-- 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 `From`. +-- This implementation eliminates certain +-- types of runtime errors by preventing the construction of +-- invalid SQL (e.g. illegal nested-@from@). +from :: ToFrom a a' => a -> SqlQuery a' +from f = do + (a, clause) <- unFrom (toFrom f) + Q $ W.tell mempty{sdFromClause=[FromRaw $ clause]} + pure a + +type RawFn = NeedParens -> IdentInfo -> (TLB.Builder, [PersistValue]) + +-- | Data type defining the "From" language. This should not +-- constructed directly in application code. +-- +-- A @From@ is a SqlQuery which returns a reference to the result of calling from +-- and a function that produces a portion of a FROM clause. This gets passed to +-- the FromRaw FromClause constructor directly when converting +-- from a @From@ to a @SqlQuery@ using @from@ +-- +-- /Since: 3.5.0.0/ +newtype From a = From + { unFrom :: SqlQuery (a, RawFn)} + + +-- | A helper class primarily designed to allow using @SqlQuery@ directly in +-- a From expression. This is also useful for embedding a @SqlSetOperation@, +-- as well as supporting backwards compatibility for the +-- data constructor join tree used prior to /3.5.0.0/ +-- +-- /Since: 3.5.0.0/ +class ToFrom a r | a -> r where + toFrom :: a -> From r +instance ToFrom (From a) a where + toFrom = id + +{-# DEPRECATED Table "/Since: 3.5.0.0/ - use 'table' instead" #-} +data Table a = Table + +instance PersistEntity ent => ToFrom (Table ent) (SqlExpr (Entity ent)) where + toFrom _ = table + +-- | Bring a PersistEntity into scope from a table +-- +-- @ +-- select $ from $ table \@People +-- @ +-- +-- /Since: 3.5.0.0/ +table :: forall ent. PersistEntity ent => From (SqlExpr (Entity ent)) +table = From $ do + let ed = entityDef (Proxy @ent) + ident <- newIdentFor (coerce $ getEntityDBName ed) + let entity = unsafeSqlEntity ident + pure $ ( entity, const $ base ident ed ) + where + base ident@(I identText) def info = + let db = coerce $ getEntityDBName def + in ( (fromDBName info (coerce db)) <> + if db == identText + then mempty + else " AS " <> useIdent info ident + , mempty + ) + + +{-# DEPRECATED SubQuery "/Since: 3.4.0.0/ - It is no longer necessary to tag 'SqlQuery' values with @SubQuery@" #-} +newtype SubQuery a = SubQuery a +instance (SqlSelect a r, ToAlias a, ToAliasReference a) => ToFrom (SubQuery (SqlQuery a)) a where + toFrom (SubQuery q) = selectQuery q +instance (SqlSelect a r, ToAlias a, ToAliasReference a) => ToFrom (SqlQuery a) a where + toFrom = selectQuery + +-- | Select from a subquery, often used in conjuction with joins but can be +-- used without any joins. Because @SqlQuery@ has a @ToFrom@ instance you probably +-- dont need to use this function directly. +-- +-- @ +-- select $ +-- p <- from $ +-- selectQuery do +-- p <- from $ table \@Person +-- limit 5 +-- orderBy [ asc p ^. PersonAge ] +-- ... +-- @ +-- +-- /Since: 3.5.0.0/ +selectQuery :: (SqlSelect a r, ToAlias a, ToAliasReference a) => SqlQuery a -> From a +selectQuery subquery = From $ do + -- We want to update the IdentState without writing the query to side data + (ret, sideData) <- Q $ W.censor (\_ -> mempty) $ W.listen $ unQ subquery + aliasedValue <- toAlias ret + -- Make a fake query with the aliased results, this allows us to ensure that the query is only run once + let aliasedQuery = Q $ W.WriterT $ pure (aliasedValue, sideData) + -- Add the FromQuery that renders the subquery to our side data + subqueryAlias <- newIdentFor (DBName "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. + ref <- toAliasReference subqueryAlias aliasedValue + + pure (ref, \_ info -> + let (queryText,queryVals) = toRawSql SELECT info aliasedQuery + in + ( (parens queryText) <> " AS " <> useIdent info subqueryAlias + , queryVals + ) + ) diff --git a/src/Database/Esqueleto/Experimental/From/CommonTableExpression.hs b/src/Database/Esqueleto/Experimental/From/CommonTableExpression.hs new file mode 100644 index 0000000..ebaa4c7 --- /dev/null +++ b/src/Database/Esqueleto/Experimental/From/CommonTableExpression.hs @@ -0,0 +1,111 @@ +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TypeFamilies #-} + +module Database.Esqueleto.Experimental.From.CommonTableExpression + where + +import qualified Control.Monad.Trans.Writer as W +import qualified Data.Text.Lazy.Builder as TLB +import Database.Esqueleto.Experimental.From +import Database.Esqueleto.Experimental.From.SqlSetOperation +import Database.Esqueleto.Experimental.ToAlias +import Database.Esqueleto.Experimental.ToAliasReference +import Database.Esqueleto.Internal.Internal hiding (From(..), from, on) + +-- | @WITH@ clause used to introduce a [Common Table Expression (CTE)](https://en.wikipedia.org/wiki/Hierarchical_and_recursive_queries_in_SQL#Common_table_expression). +-- CTEs are supported in most modern SQL engines and can be useful +-- in performance tuning. In Esqueleto, CTEs should be used as a +-- subquery memoization tactic. When writing plain SQL, CTEs +-- are sometimes used to organize the SQL code, in Esqueleto, this +-- is better achieved through function that return 'SqlQuery' values. +-- +-- @ +-- select $ do +-- cte <- with subQuery +-- cteResult <- from cte +-- where_ $ cteResult ... +-- pure cteResult +-- @ +-- +-- __WARNING__: In some SQL engines using a CTE can diminish performance. +-- In these engines the CTE is treated as an optimization fence. You should +-- always verify that using a CTE will in fact improve your performance +-- over a regular subquery. +-- +-- /Since: 3.4.0.0/ +with :: ( ToAlias a + , ToAliasReference a + , SqlSelect a r + ) => SqlQuery a -> SqlQuery (From a) +with query = do + (ret, sideData) <- Q $ W.censor (\_ -> mempty) $ W.listen $ unQ query + aliasedValue <- toAlias ret + let aliasedQuery = Q $ W.WriterT $ pure (aliasedValue, sideData) + ident <- newIdentFor (DBName "cte") + let clause = CommonTableExpressionClause NormalCommonTableExpression ident (\info -> toRawSql SELECT info aliasedQuery) + Q $ W.tell mempty{sdCteClause = [clause]} + ref <- toAliasReference ident aliasedValue + pure $ From $ pure (ref, (\_ info -> (useIdent info ident, mempty))) + +-- | @WITH@ @RECURSIVE@ allows one to make a recursive subquery, which can +-- reference itself. Like @WITH@, this is supported in most modern SQL engines. +-- Useful for hierarchical, self-referential data, like a tree of data. +-- +-- @ +-- select $ do +-- cte <- withRecursive +-- (do +-- person <- from $ table \@Person +-- where_ $ person ^. PersonId ==. val personId +-- pure person +-- ) +-- unionAll_ +-- (\\self -> do +-- (p :& f :& p2 :& pSelf) <- from self +-- \`innerJoin\` $ table \@Follow +-- \`on\` (\\(p :& f) -> +-- p ^. PersonId ==. f ^. FollowFollower) +-- \`innerJoin\` $ table \@Person +-- \`on\` (\\(p :& f :& p2) -> +-- f ^. FollowFollowed ==. p2 ^. PersonId) +-- \`leftJoin\` self +-- \`on\` (\\(_ :& _ :& p2 :& pSelf) -> +-- just (p2 ^. PersonId) ==. pSelf ?. PersonId) +-- where_ $ isNothing (pSelf ?. PersonId) +-- groupBy (p2 ^. PersonId) +-- pure p2 +-- ) +-- from cte +-- @ +-- +-- /Since: 3.4.0.0/ +withRecursive :: ( ToAlias a + , ToAliasReference a + , SqlSelect a r + ) + => SqlQuery a + -> UnionKind + -> (From a -> SqlQuery a) + -> SqlQuery (From a) +withRecursive baseCase unionKind recursiveCase = do + (ret, sideData) <- Q $ W.censor (\_ -> mempty) $ W.listen $ unQ baseCase + aliasedValue <- toAlias ret + let aliasedQuery = Q $ W.WriterT $ pure (aliasedValue, sideData) + ident <- newIdentFor (DBName "cte") + ref <- toAliasReference ident aliasedValue + let refFrom = From (pure (ref, (\_ info -> (useIdent info ident, mempty)))) + let recursiveQuery = recursiveCase refFrom + let clause = CommonTableExpressionClause RecursiveCommonTableExpression ident + (\info -> (toRawSql SELECT info aliasedQuery) + <> ("\n" <> (unUnionKind unionKind) <> "\n", mempty) + <> (toRawSql SELECT info recursiveQuery) + ) + Q $ W.tell mempty{sdCteClause = [clause]} + pure refFrom + +newtype UnionKind = UnionKind { unUnionKind :: TLB.Builder } +instance Union_ UnionKind where + union_ = UnionKind "UNION" +instance UnionAll_ UnionKind where + unionAll_ = UnionKind "UNION ALL" diff --git a/src/Database/Esqueleto/Experimental/From/Join.hs b/src/Database/Esqueleto/Experimental/From/Join.hs new file mode 100644 index 0000000..c685adc --- /dev/null +++ b/src/Database/Esqueleto/Experimental/From/Join.hs @@ -0,0 +1,407 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE FunctionalDependencies #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE UndecidableInstances #-} + +module Database.Esqueleto.Experimental.From.Join + where + +import Data.Bifunctor (first) +import Data.Kind (Constraint) +import Data.Proxy +import qualified Data.Text.Lazy.Builder as TLB +import Database.Esqueleto.Experimental.From +import Database.Esqueleto.Experimental.From.SqlSetOperation +import Database.Esqueleto.Experimental.ToAlias +import Database.Esqueleto.Experimental.ToAliasReference +import Database.Esqueleto.Experimental.ToMaybe +import Database.Esqueleto.Internal.Internal hiding + (From (..), + from, + fromJoin, + on) +import Database.Esqueleto.Internal.PersistentImport (Entity (..), + EntityField, + PersistEntity, + PersistField) +import GHC.TypeLits + +-- | 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 :& + +instance (ToMaybe a, ToMaybe b) => ToMaybe (a :& b) where + type ToMaybeT (a :& b) = (ToMaybeT a :& ToMaybeT b) + toMaybe (a :& b) = (toMaybe a :& toMaybe b) + +class ValidOnClause a +instance {-# OVERLAPPABLE #-} ToFrom a a' => ValidOnClause a +instance ValidOnClause (a -> SqlQuery 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 :: ValidOnClause a => a -> (b -> SqlExpr (Value Bool)) -> (a, b -> SqlExpr (Value Bool)) +on = (,) +infix 9 `on` + +type family ErrorOnLateral a :: Constraint where + ErrorOnLateral (a -> SqlQuery b) = TypeError ('Text "LATERAL can only be used for INNER, LEFT, and CROSS join kinds.") + ErrorOnLateral _ = () + +fromJoin :: TLB.Builder -> RawFn -> RawFn -> Maybe (SqlExpr (Value Bool)) -> RawFn +fromJoin joinKind lhs rhs monClause = + \paren info -> + first (parensM paren) $ + mconcat [ lhs Never info + , (joinKind, mempty) + , rhs Parens info + , maybe mempty (makeOnClause info) monClause + ] + where + makeOnClause info (ERaw _ f) = first (" ON " <>) (f Never info) + +type family HasOnClause actual expected :: Constraint where + HasOnClause (a, b -> SqlExpr (Value Bool)) c = () -- Let the compiler handle the type mismatch + HasOnClause a expected = + TypeError ( 'Text "Missing ON clause for join with" + ':$$: 'ShowType a + ':$$: 'Text "" + ':$$: 'Text "Expected: " + ':$$: 'ShowType a + ':$$: 'Text "`on` " ':<>: 'ShowType (expected -> SqlExpr (Value Bool)) + ':$$: 'Text "" + ) + + +-- | INNER JOIN +-- +-- Used as an infix operator \`innerJoin\` +-- +-- @ +-- select $ +-- from $ table \@Person +-- \`innerJoin\` table \@BlogPost +-- \`on\` (\\(p :& bp) -> +-- p ^. PersonId ==. bp ^. BlogPostAuthorId) +-- @ +-- +-- /Since: 3.5.0.0/ +innerJoin :: ( ToFrom a a' + , ToFrom b b' + , HasOnClause rhs (a' :& b') + , rhs ~ (b, (a' :& b') -> SqlExpr (Value Bool)) + ) => a -> rhs -> From (a' :& b') +innerJoin lhs (rhs, on') = From $ do + (leftVal, leftFrom) <- unFrom (toFrom lhs) + (rightVal, rightFrom) <- unFrom (toFrom rhs) + let ret = leftVal :& rightVal + pure $ (ret, fromJoin " INNER JOIN " leftFrom rightFrom (Just $ on' ret)) + + +-- | INNER JOIN LATERAL +-- +-- A Lateral subquery join allows the joined query to reference entities from the +-- left hand side of the join. Discards rows that don't match the on clause +-- +-- Used as an infix operator \`innerJoinLateral\` +-- +-- See example 6 +-- +-- /Since: 3.5.0.0/ +innerJoinLateral :: ( ToFrom a a' + , HasOnClause rhs (a' :& b) + , SqlSelect b r + , ToAlias b + , ToAliasReference b + , rhs ~ (a' -> SqlQuery b, (a' :& b) -> SqlExpr (Value Bool)) + ) + => a -> rhs -> From (a' :& b) +innerJoinLateral lhs (rhsFn, on') = From $ do + (leftVal, leftFrom) <- unFrom (toFrom lhs) + (rightVal, rightFrom) <- unFrom (selectQuery (rhsFn leftVal)) + let ret = leftVal :& rightVal + pure $ (ret, fromJoin " INNER JOIN LATERAL " leftFrom rightFrom (Just $ on' ret)) + +-- | CROSS JOIN +-- +-- Used as an infix \`crossJoin\` +-- +-- @ +-- select $ do +-- from $ table \@Person +-- \`crossJoin\` table \@BlogPost +-- @ +-- +-- /Since: 3.5.0.0/ +crossJoin :: ( ToFrom a a' + , ToFrom b b' + ) => a -> b -> From (a' :& b') +crossJoin lhs rhs = From $ do + (leftVal, leftFrom) <- unFrom (toFrom lhs) + (rightVal, rightFrom) <- unFrom (toFrom rhs) + let ret = leftVal :& rightVal + pure $ (ret, fromJoin " CROSS JOIN " leftFrom rightFrom Nothing) + +-- | CROSS JOIN LATERAL +-- +-- A Lateral subquery join allows the joined query to reference entities from the +-- left hand side of the join. +-- +-- Used as an infix operator \`crossJoinLateral\` +-- +-- See example 6 +-- +-- /Since: 3.5.0.0/ +crossJoinLateral :: ( ToFrom a a' + , SqlSelect b r + , ToAlias b + , ToAliasReference b + ) + => a -> (a' -> SqlQuery b) -> From (a' :& b) +crossJoinLateral lhs rhsFn = From $ do + (leftVal, leftFrom) <- unFrom (toFrom lhs) + (rightVal, rightFrom) <- unFrom (selectQuery (rhsFn leftVal)) + let ret = leftVal :& rightVal + pure $ (ret, fromJoin " CROSS JOIN LATERAL " leftFrom rightFrom Nothing) + +-- | LEFT OUTER JOIN +-- +-- Join where the right side may not exist. +-- If the on clause fails then the right side will be NULL'ed +-- Because of this the right side needs to be handled as a Maybe +-- +-- Used as an infix operator \`leftJoin\` +-- +-- @ +-- select $ +-- from $ table \@Person +-- \`leftJoin\` table \@BlogPost +-- \`on\` (\\(p :& bp) -> +-- p ^. PersonId ==. bp ?. BlogPostAuthorId) +-- @ +-- +-- /Since: 3.5.0.0/ +leftJoin :: ( ToFrom a a' + , ToFrom b b' + , ToMaybe b' + , HasOnClause rhs (a' :& ToMaybeT b') + , rhs ~ (b, (a' :& ToMaybeT b') -> SqlExpr (Value Bool)) + ) => a -> rhs -> From (a' :& ToMaybeT b') +leftJoin lhs (rhs, on') = From $ do + (leftVal, leftFrom) <- unFrom (toFrom lhs) + (rightVal, rightFrom) <- unFrom (toFrom rhs) + let ret = leftVal :& toMaybe rightVal + pure $ (ret, fromJoin " LEFT OUTER JOIN " leftFrom rightFrom (Just $ on' ret)) + +-- | LEFT OUTER JOIN LATERAL +-- +-- Lateral join where the right side may not exist. +-- In the case that the query returns nothing or the on clause fails the right +-- side of the join will be NULL'ed +-- Because of this the right side needs to be handled as a Maybe +-- +-- Used as an infix operator \`leftJoinLateral\` +-- +-- See example 6 for how to use LATERAL +-- +-- /Since: 3.5.0.0/ +leftJoinLateral :: ( ToFrom a a' + , SqlSelect b r + , HasOnClause rhs (a' :& ToMaybeT b) + , ToAlias b + , ToAliasReference b + , ToMaybe b + , rhs ~ (a' -> SqlQuery b, (a' :& ToMaybeT b) -> SqlExpr (Value Bool)) + ) + => a -> rhs -> From (a' :& ToMaybeT b) +leftJoinLateral lhs (rhsFn, on') = From $ do + (leftVal, leftFrom) <- unFrom (toFrom lhs) + (rightVal, rightFrom) <- unFrom (selectQuery (rhsFn leftVal)) + let ret = leftVal :& toMaybe rightVal + pure $ (ret, fromJoin " LEFT OUTER JOIN LATERAL " leftFrom rightFrom (Just $ on' ret)) + +-- | RIGHT OUTER JOIN +-- +-- Join where the left side may not exist. +-- If the on clause fails then the left side will be NULL'ed +-- Because of this the left side needs to be handled as a Maybe +-- +-- Used as an infix operator \`rightJoin\` +-- +-- @ +-- select $ +-- from $ table \@Person +-- \`rightJoin\` table \@BlogPost +-- \`on\` (\\(p :& bp) -> +-- p ?. PersonId ==. bp ^. BlogPostAuthorId) +-- @ +-- +-- /Since: 3.5.0.0/ +rightJoin :: ( ToFrom a a' + , ToFrom b b' + , ToMaybe a' + , HasOnClause rhs (ToMaybeT a' :& b') + , rhs ~ (b, (ToMaybeT a' :& b') -> SqlExpr (Value Bool)) + ) => a -> rhs -> From (ToMaybeT a' :& b') +rightJoin lhs (rhs, on') = From $ do + (leftVal, leftFrom) <- unFrom (toFrom lhs) + (rightVal, rightFrom) <- unFrom (toFrom rhs) + let ret = toMaybe leftVal :& rightVal + pure $ (ret, fromJoin " RIGHT OUTER JOIN " leftFrom rightFrom (Just $ on' ret)) + +-- | FULL OUTER JOIN +-- +-- Join where both sides of the join may not exist. +-- Because of this the result needs to be handled as a Maybe +-- +-- Used as an infix operator \`fullOuterJoin\` +-- +-- @ +-- select $ +-- from $ table \@Person +-- \`fullOuterJoin\` table \@BlogPost +-- \`on\` (\\(p :& bp) -> +-- p ?. PersonId ==. bp ?. BlogPostAuthorId) +-- @ +-- +-- /Since: 3.5.0.0/ +fullOuterJoin :: ( ToFrom a a' + , ToFrom b b' + , ToMaybe a' + , ToMaybe b' + , HasOnClause rhs (ToMaybeT a' :& ToMaybeT b') + , rhs ~ (b, (ToMaybeT a' :& ToMaybeT b') -> SqlExpr (Value Bool)) + ) => a -> rhs -> From (ToMaybeT a' :& ToMaybeT b') +fullOuterJoin lhs (rhs, on') = From $ do + (leftVal, leftFrom) <- unFrom (toFrom lhs) + (rightVal, rightFrom) <- unFrom (toFrom rhs) + let ret = toMaybe leftVal :& toMaybe rightVal + pure $ (ret, fromJoin " FULL OUTER JOIN " leftFrom rightFrom (Just $ on' ret)) + +infixl 2 `innerJoin`, + `innerJoinLateral`, + `leftJoin`, + `leftJoinLateral`, + `crossJoin`, + `crossJoinLateral`, + `rightJoin`, + `fullOuterJoin` + + +------ Compatibility for old syntax + +data Lateral +data NotLateral + +type family IsLateral a where + IsLateral (a -> SqlQuery b, c) = Lateral + IsLateral (a -> SqlQuery b) = Lateral + IsLateral a = NotLateral + +class DoInnerJoin lateral lhs rhs res | lateral rhs lhs -> res where + doInnerJoin :: Proxy lateral -> lhs -> rhs -> From res + +instance ( ToFrom a a' + , ToFrom b b' + , HasOnClause rhs (a' :& b') + , rhs ~ (b, (a' :& b') -> SqlExpr (Value Bool)) + ) => DoInnerJoin NotLateral a rhs (a' :& b') where + doInnerJoin _ = innerJoin + +instance ( ToFrom a a' + , SqlSelect b r + , ToAlias b + , ToAliasReference b + , d ~ (a' :& b) + ) => DoInnerJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d where + doInnerJoin _ = innerJoinLateral + +instance ( DoInnerJoin lateral lhs rhs r, lateral ~ IsLateral rhs ) + => ToFrom (InnerJoin lhs rhs) r where + toFrom (InnerJoin a b) = doInnerJoin (Proxy @lateral) a b + +class DoLeftJoin lateral lhs rhs res | lateral rhs lhs -> res where + doLeftJoin :: Proxy lateral -> lhs -> rhs -> From res + +instance ( ToFrom a a' + , ToFrom b b' + , ToMaybe b' + , ToMaybeT b' ~ mb + , HasOnClause rhs (a' :& mb) + , rhs ~ (b, (a' :& mb) -> SqlExpr (Value Bool)) + ) => DoLeftJoin NotLateral a rhs (a' :& mb) where + doLeftJoin _ = leftJoin + +instance ( ToFrom a a' + , ToMaybe b + , d ~ (a' :& ToMaybeT b) + , SqlSelect b r + , ToAlias b + , ToAliasReference b + ) => DoLeftJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d where + doLeftJoin _ = leftJoinLateral + +instance ( DoLeftJoin lateral lhs rhs r, lateral ~ IsLateral rhs ) + => ToFrom (LeftOuterJoin lhs rhs) r where + toFrom (LeftOuterJoin a b) = doLeftJoin (Proxy @lateral) a b + +class DoCrossJoin lateral lhs rhs res | lateral lhs rhs -> res where + doCrossJoin :: Proxy lateral -> lhs -> rhs -> From res + +instance (ToFrom a a', ToFrom b b') => DoCrossJoin NotLateral a b (a' :& b') where + doCrossJoin _ = crossJoin +instance (ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b) + => DoCrossJoin Lateral a (a' -> SqlQuery b) (a' :& b) where + doCrossJoin _ = crossJoinLateral + +instance (DoCrossJoin lateral lhs rhs r, IsLateral rhs ~ lateral) + => ToFrom (CrossJoin lhs rhs) r where + toFrom (CrossJoin a b) = doCrossJoin (Proxy @lateral) a b + +instance ( ToFrom a a' + , ToFrom b b' + , ToMaybe a' + , ToMaybeT a' ~ ma + , HasOnClause rhs (ma :& b') + , ErrorOnLateral b + , rhs ~ (b, (ma :& b') -> SqlExpr (Value Bool)) + ) => ToFrom (RightOuterJoin a rhs) (ma :& b') where + toFrom (RightOuterJoin a b) = rightJoin a b + +instance ( ToFrom a a' + , ToFrom b b' + , ToMaybe a' + , ToMaybeT a' ~ ma + , ToMaybe b' + , ToMaybeT b' ~ mb + , HasOnClause rhs (ma :& mb) + , ErrorOnLateral b + , rhs ~ (b, (ma :& mb) -> SqlExpr (Value Bool)) + ) => ToFrom (FullOuterJoin a rhs) (ma :& mb) where + toFrom (FullOuterJoin a b) = fullOuterJoin a b + diff --git a/src/Database/Esqueleto/Experimental/From/SqlSetOperation.hs b/src/Database/Esqueleto/Experimental/From/SqlSetOperation.hs new file mode 100644 index 0000000..943055b --- /dev/null +++ b/src/Database/Esqueleto/Experimental/From/SqlSetOperation.hs @@ -0,0 +1,131 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE FunctionalDependencies #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE UndecidableInstances #-} + +module Database.Esqueleto.Experimental.From.SqlSetOperation + where + +import Control.Arrow (first) +import Control.Monad.Trans.Class (lift) +import qualified Control.Monad.Trans.State as S +import qualified Control.Monad.Trans.Writer as W +import qualified Data.Text.Lazy.Builder as TLB +import Database.Esqueleto.Experimental.From +import Database.Esqueleto.Experimental.ToAlias +import Database.Esqueleto.Experimental.ToAliasReference +import Database.Esqueleto.Internal.Internal hiding (From(..), from, on) +import Database.Esqueleto.Internal.PersistentImport + (Entity, PersistEntity, PersistValue) + +-- | Data type used to implement the SqlSetOperation language +-- this type is implemented in the same way as a @From@ +-- +-- Semantically a @SqlSetOperation@ is always a @From@ but not vice versa +-- +-- /Since: 3.5.0.0/ +newtype SqlSetOperation a = SqlSetOperation + { unSqlSetOperation :: NeedParens -> SqlQuery (a, IdentInfo -> (TLB.Builder, [PersistValue]))} + +instance ToAliasReference a => ToFrom (SqlSetOperation a) a where + toFrom setOperation = From $ do + ident <- newIdentFor (DBName "u") + (a, fromClause) <- unSqlSetOperation setOperation Never + ref <- toAliasReference ident a + pure (ref, \_ info -> (first parens $ fromClause info) <> (" AS " <> useIdent info ident, mempty)) + +-- | Type class to support direct use of @SqlQuery@ in a set operation tree +-- +-- /Since: 3.5.0.0/ +class ToSqlSetOperation a r | a -> r where + toSqlSetOperation :: a -> SqlSetOperation r +instance ToSqlSetOperation (SqlSetOperation a) a where + toSqlSetOperation = id +instance (SqlSelect a r, ToAlias a, ToAliasReference a) => ToSqlSetOperation (SqlQuery a) a where + toSqlSetOperation subquery = + SqlSetOperation $ \p -> do + (ret, sideData) <- Q $ W.censor (\_ -> mempty) $ W.listen $ unQ subquery + state <- Q $ lift S.get + aliasedValue <- toAlias ret + Q $ lift $ S.put state + let aliasedQuery = Q $ W.WriterT $ pure (aliasedValue, sideData) + let p' = + case p of + Parens -> Parens + Never -> + if (sdLimitClause sideData) /= mempty + || length (sdOrderByClause sideData) > 0 then + Parens + else + Never + pure (aliasedValue, \info -> first (parensM p') $ toRawSql SELECT info aliasedQuery) + +-- | Helper function for defining set operations +-- /Since: 3.5.0.0/ +mkSetOperation :: (ToSqlSetOperation a a', ToSqlSetOperation b a') + => TLB.Builder -> a -> b -> SqlSetOperation a' +mkSetOperation operation lhs rhs = SqlSetOperation $ \p -> do + (leftValue, leftClause) <- unSqlSetOperation (toSqlSetOperation lhs) p + (_, rightClause) <- unSqlSetOperation (toSqlSetOperation rhs) p + pure (leftValue, \info -> leftClause info <> (operation, mempty) <> rightClause info) + +{-# DEPRECATED Union "/Since: 3.4.0.0/ - Use the 'union_' function instead of the 'Union' data constructor" #-} +data Union a b = a `Union` b +instance ToSqlSetOperation a a' => ToSqlSetOperation (Union a a) a' where + toSqlSetOperation (Union a b) = union_ a b + +-- | Overloaded @union_@ function to support use in both 'SqlSetOperation' +-- and 'withRecursive' +-- +-- /Since: 3.5.0.0/ +class Union_ a where + -- | @UNION@ SQL set operation. Can be used as an infix function between 'SqlQuery' values. + union_ :: a + +instance (ToSqlSetOperation a c, ToSqlSetOperation b c, res ~ SqlSetOperation c) + => Union_ (a -> b -> res) where + union_ = mkSetOperation " UNION " + +-- | Overloaded @unionAll_@ function to support use in both 'SqlSetOperation' +-- and 'withRecursive' +-- +-- /Since: 3.5.0.0/ +class UnionAll_ a where + -- | @UNION@ @ALL@ SQL set operation. Can be used as an infix function between 'SqlQuery' values. + unionAll_ :: a +instance (ToSqlSetOperation a c, ToSqlSetOperation b c, res ~ SqlSetOperation c) + => UnionAll_ (a -> b -> res) where + unionAll_ = mkSetOperation " UNION ALL " + +{-# DEPRECATED UnionAll "/Since: 3.4.0.0/ - Use the 'unionAll_' function instead of the 'UnionAll' data constructor" #-} +data UnionAll a b = a `UnionAll` b +instance ToSqlSetOperation a a' => ToSqlSetOperation (UnionAll a a) a' where + toSqlSetOperation (UnionAll a b) = unionAll_ a b + +{-# DEPRECATED Except "/Since: 3.4.0.0/ - Use the 'except_' function instead of the 'Except' data constructor" #-} +data Except a b = a `Except` b +instance ToSqlSetOperation a a' => ToSqlSetOperation (Except a a) a' where + toSqlSetOperation (Except a b) = except_ a b + +-- | @EXCEPT@ SQL set operation. Can be used as an infix function between 'SqlQuery' values. +except_ :: (ToSqlSetOperation a a', ToSqlSetOperation b a') => a -> b -> SqlSetOperation a' +except_ = mkSetOperation " EXCEPT " + +{-# DEPRECATED Intersect "/Since: 3.4.0.0/ - Use the 'intersect_' function instead of the 'Intersect' data constructor" #-} +data Intersect a b = a `Intersect` b +instance ToSqlSetOperation a a' => ToSqlSetOperation (Intersect a a) a' where + toSqlSetOperation (Intersect a b) = intersect_ a b + +-- | @INTERSECT@ SQL set operation. Can be used as an infix function between 'SqlQuery' values. +intersect_ :: (ToSqlSetOperation a a', ToSqlSetOperation b a') => a -> b -> SqlSetOperation a' +intersect_ = mkSetOperation " INTERSECT " + +{-# DEPRECATED SelectQuery "/Since: 3.4.0.0/ - It is no longer necessary to tag 'SqlQuery' values with @SelectQuery@" #-} +pattern SelectQuery a = a + diff --git a/src/Database/Esqueleto/Experimental/ToAlias.hs b/src/Database/Esqueleto/Experimental/ToAlias.hs new file mode 100644 index 0000000..b6ab991 --- /dev/null +++ b/src/Database/Esqueleto/Experimental/ToAlias.hs @@ -0,0 +1,92 @@ +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TypeFamilies #-} + +module Database.Esqueleto.Experimental.ToAlias + where + +import Database.Esqueleto.Internal.Internal hiding (From, from, on) +import Database.Esqueleto.Internal.PersistentImport + +{-# DEPRECATED ToAliasT "This type alias doesn't do anything. Please delete it. Will be removed in the next release." #-} +type ToAliasT a = a + +-- Tedious tuple magic +class ToAlias a where + toAlias :: a -> SqlQuery a + +instance ToAlias (SqlExpr (Value a)) where + toAlias e@(ERaw m f) + | Just _ <- sqlExprMetaAlias m = pure e + | otherwise = do + ident <- newIdentFor (DBName "v") + pure $ ERaw noMeta{sqlExprMetaAlias = Just ident} f + +instance ToAlias (SqlExpr (Entity a)) where + toAlias e@(ERaw m f) + | Just _ <- sqlExprMetaAlias m = pure e + | otherwise = do + ident <- newIdentFor (DBName "v") + pure $ ERaw m{sqlExprMetaIsReference = False, sqlExprMetaAlias = Just ident} f + +instance ToAlias (SqlExpr (Maybe (Entity a))) where + -- FIXME: Code duplication because the compiler doesnt like half final encoding + toAlias e@(ERaw m f) + | Just _ <- sqlExprMetaAlias m = pure e + | otherwise = do + ident <- newIdentFor (DBName "v") + pure $ ERaw m{sqlExprMetaIsReference = False, sqlExprMetaAlias = Just ident} f + +instance (ToAlias a, ToAlias b) => ToAlias (a,b) where + toAlias (a,b) = (,) <$> toAlias a <*> toAlias b + +instance ( ToAlias a + , ToAlias b + , ToAlias c + ) => ToAlias (a,b,c) where + toAlias x = to3 <$> (toAlias $ from3 x) + +instance ( ToAlias a + , ToAlias b + , ToAlias c + , ToAlias d + ) => ToAlias (a,b,c,d) where + toAlias x = to4 <$> (toAlias $ from4 x) + +instance ( ToAlias a + , ToAlias b + , ToAlias c + , ToAlias d + , ToAlias e + ) => ToAlias (a,b,c,d,e) where + toAlias x = to5 <$> (toAlias $ from5 x) + +instance ( ToAlias a + , ToAlias b + , ToAlias c + , ToAlias d + , ToAlias e + , ToAlias f + ) => ToAlias (a,b,c,d,e,f) where + toAlias x = to6 <$> (toAlias $ from6 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 x = to7 <$> (toAlias $ from7 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 x = to8 <$> (toAlias $ from8 x) diff --git a/src/Database/Esqueleto/Experimental/ToAliasReference.hs b/src/Database/Esqueleto/Experimental/ToAliasReference.hs new file mode 100644 index 0000000..4d843ad --- /dev/null +++ b/src/Database/Esqueleto/Experimental/ToAliasReference.hs @@ -0,0 +1,90 @@ +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TypeFamilies #-} + +module Database.Esqueleto.Experimental.ToAliasReference + where + +import Data.Coerce +import Database.Esqueleto.Internal.Internal hiding (From, from, on) +import Database.Esqueleto.Internal.PersistentImport + +{-# DEPRECATED ToAliasReferenceT "This type alias doesn't do anything. Please delete it. Will be removed in the next release." #-} +type ToAliasReferenceT a = a + +-- more tedious tuple magic +class ToAliasReference a where + toAliasReference :: Ident -> a -> SqlQuery a + +instance ToAliasReference (SqlExpr (Value a)) where + toAliasReference aliasSource (ERaw m _) + | Just alias <- sqlExprMetaAlias m = pure $ ERaw m{sqlExprMetaIsReference = True} $ \_ info -> + (useIdent info aliasSource <> "." <> useIdent info alias, []) + toAliasReference _ e = pure e + +instance ToAliasReference (SqlExpr (Entity a)) where + toAliasReference aliasSource (ERaw m _) + | Just _ <- sqlExprMetaAlias m = + pure $ ERaw m{sqlExprMetaIsReference = True} $ \_ info -> + (useIdent info aliasSource, []) + toAliasReference _ e = pure e + +instance ToAliasReference (SqlExpr (Maybe (Entity a))) where + toAliasReference aliasSource e = + coerce <$> toAliasReference aliasSource (coerce e :: SqlExpr (Entity a)) + + +instance (ToAliasReference a, ToAliasReference b) => ToAliasReference (a, b) where + toAliasReference ident (a,b) = (,) <$> (toAliasReference ident a) <*> (toAliasReference ident b) + +instance ( ToAliasReference a + , ToAliasReference b + , ToAliasReference c + ) => ToAliasReference (a,b,c) where + toAliasReference ident x = fmap to3 $ toAliasReference ident $ from3 x + +instance ( ToAliasReference a + , ToAliasReference b + , ToAliasReference c + , ToAliasReference d + ) => ToAliasReference (a,b,c,d) where + toAliasReference ident x = fmap to4 $ toAliasReference ident $ from4 x + +instance ( ToAliasReference a + , ToAliasReference b + , ToAliasReference c + , ToAliasReference d + , ToAliasReference e + ) => ToAliasReference (a,b,c,d,e) where + toAliasReference ident x = fmap to5 $ toAliasReference ident $ from5 x + +instance ( ToAliasReference a + , ToAliasReference b + , ToAliasReference c + , ToAliasReference d + , ToAliasReference e + , ToAliasReference f + ) => ToAliasReference (a,b,c,d,e,f) where + toAliasReference ident x = to6 <$> (toAliasReference ident $ from6 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 x = to7 <$> (toAliasReference ident $ from7 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 x = to8 <$> (toAliasReference ident $ from8 x) + diff --git a/src/Database/Esqueleto/Experimental/ToMaybe.hs b/src/Database/Esqueleto/Experimental/ToMaybe.hs new file mode 100644 index 0000000..0677bfb --- /dev/null +++ b/src/Database/Esqueleto/Experimental/ToMaybe.hs @@ -0,0 +1,79 @@ +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE TypeFamilies #-} + +module Database.Esqueleto.Experimental.ToMaybe + where + +import Database.Esqueleto.Internal.Internal hiding (From(..), from, on) +import Database.Esqueleto.Internal.PersistentImport (Entity(..)) + +type family Nullable a where + Nullable (Maybe a) = a + Nullable a = a + +class ToMaybe a where + type ToMaybeT a + toMaybe :: a -> ToMaybeT a + +instance ToMaybe (SqlExpr (Maybe a)) where + type ToMaybeT (SqlExpr (Maybe a)) = SqlExpr (Maybe a) + toMaybe = id + +instance ToMaybe (SqlExpr (Entity a)) where + type ToMaybeT (SqlExpr (Entity a)) = SqlExpr (Maybe (Entity a)) + toMaybe (ERaw f m) = (ERaw f m) + +instance ToMaybe (SqlExpr (Value a)) where + type ToMaybeT (SqlExpr (Value a)) = SqlExpr (Value (Maybe (Nullable a))) + toMaybe = veryUnsafeCoerceSqlExprValue + + +instance (ToMaybe a, ToMaybe b) => ToMaybe (a,b) where + type ToMaybeT (a, b) = (ToMaybeT a, ToMaybeT b) + toMaybe (a, b) = (toMaybe a, toMaybe b) + +instance ( ToMaybe a , ToMaybe b , ToMaybe c) => ToMaybe (a,b,c) where + type ToMaybeT (a, b, c) = (ToMaybeT a, ToMaybeT b, ToMaybeT c) + toMaybe = to3 . toMaybe . from3 + +instance ( ToMaybe a , ToMaybe b , ToMaybe c , ToMaybe d) => ToMaybe (a,b,c,d) where + type ToMaybeT (a, b, c, d) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d) + toMaybe = to4 . toMaybe . from4 + +instance ( ToMaybe a , ToMaybe b , ToMaybe c , ToMaybe d , ToMaybe e) => ToMaybe (a,b,c,d,e) where + type ToMaybeT (a, b, c, d, e) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e) + toMaybe = to5 . toMaybe . from5 + +instance ( ToMaybe a + , ToMaybe b + , ToMaybe c + , ToMaybe d + , ToMaybe e + , ToMaybe f + ) => ToMaybe (a,b,c,d,e,f) where + type ToMaybeT (a, b, c, d, e, f) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e, ToMaybeT f) + toMaybe = to6 . toMaybe . 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 + type ToMaybeT (a, b, c, d, e, f, g) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e, ToMaybeT f, ToMaybeT g) + toMaybe = to7 . toMaybe . 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 + type 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) + toMaybe = to8 . toMaybe . from8 + diff --git a/src/Database/Esqueleto/Internal/Internal.hs b/src/Database/Esqueleto/Internal/Internal.hs index 82cb42b..5ee850c 100644 --- a/src/Database/Esqueleto/Internal/Internal.hs +++ b/src/Database/Esqueleto/Internal/Internal.hs @@ -28,6 +28,7 @@ module Database.Esqueleto.Internal.Internal where import Data.List.NonEmpty (NonEmpty(..)) import qualified Data.List.NonEmpty as NEL import Control.Applicative ((<|>)) +import Data.Coerce (Coercible, coerce) import Control.Arrow (first, (***)) import Control.Exception (Exception, throw, throwIO) import Control.Monad (MonadPlus(..), guard, void) @@ -90,13 +91,13 @@ fromStart ( PersistEntity a , BackendCompatible SqlBackend (PersistEntityBackend a) ) - => SqlQuery (SqlExpr (PreprocessedFrom (SqlExpr (Entity a)))) + => SqlQuery (PreprocessedFrom (SqlExpr (Entity a))) fromStart = do let ed = entityDef (Proxy :: Proxy a) ident <- newIdentFor (coerce $ getEntityDBName ed) - let ret = EEntity ident + let ret = unsafeSqlEntity ident f' = FromStart ident ed - return (EPreprocessedFrom ret f') + return (PreprocessedFrom ret f') -- | Copied from @persistent@ newtype DBName = DBName { unDBName :: T.Text } @@ -106,22 +107,22 @@ fromStartMaybe :: ( PersistEntity a , BackendCompatible SqlBackend (PersistEntityBackend a) ) - => SqlQuery (SqlExpr (PreprocessedFrom (SqlExpr (Maybe (Entity a))))) + => SqlQuery (PreprocessedFrom (SqlExpr (Maybe (Entity a)))) fromStartMaybe = maybelize <$> fromStart where maybelize - :: SqlExpr (PreprocessedFrom (SqlExpr (Entity a))) - -> SqlExpr (PreprocessedFrom (SqlExpr (Maybe (Entity a)))) - maybelize (EPreprocessedFrom ret f') = EPreprocessedFrom (EMaybe ret) f' + :: PreprocessedFrom (SqlExpr (Entity a)) + -> PreprocessedFrom (SqlExpr (Maybe (Entity a))) + maybelize (PreprocessedFrom e f') = PreprocessedFrom (coerce e) f' -- | (Internal) Do a @JOIN@. fromJoin :: IsJoinKind join - => SqlExpr (PreprocessedFrom a) - -> SqlExpr (PreprocessedFrom b) - -> SqlQuery (SqlExpr (PreprocessedFrom (join a b))) -fromJoin (EPreprocessedFrom lhsRet lhsFrom) - (EPreprocessedFrom rhsRet rhsFrom) = Q $ do + => PreprocessedFrom a + -> PreprocessedFrom b + -> SqlQuery (PreprocessedFrom (join a b)) +fromJoin (PreprocessedFrom lhsRet lhsFrom) + (PreprocessedFrom rhsRet rhsFrom) = Q $ do let ret = smartJoin lhsRet rhsRet from' = FromJoin @@ -129,13 +130,13 @@ fromJoin (EPreprocessedFrom lhsRet lhsFrom) (reifyJoinKind ret) -- JOIN rhsFrom -- RHS Nothing -- ON - return (EPreprocessedFrom ret from') + return (PreprocessedFrom ret from') -- | (Internal) Finish a @JOIN@. fromFinish - :: SqlExpr (PreprocessedFrom a) + :: PreprocessedFrom a -> SqlQuery a -fromFinish (EPreprocessedFrom ret f') = Q $ do +fromFinish (PreprocessedFrom ret f') = Q $ do W.tell mempty { sdFromClause = [f'] } return ret @@ -259,11 +260,22 @@ orderBy exprs = Q $ W.tell mempty { sdOrderByClause = exprs } -- | Ascending order of this field or SqlExpression. asc :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy -asc = EOrderBy ASC +asc = orderByExpr " ASC" -- | Descending order of this field or SqlExpression. desc :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy -desc = EOrderBy DESC +desc = orderByExpr " DESC" + +orderByExpr :: TLB.Builder -> SqlExpr (Value a) -> SqlExpr OrderBy +orderByExpr orderByType (ERaw m f) + | Just fields <- sqlExprMetaCompositeFields m = + ERaw noMeta $ \_ info -> + let fs = fields info + vals = repeat [] + in uncommas' $ zip (map (<> orderByType) fs) vals + | otherwise = + ERaw noMeta $ \_ info -> + first (<> orderByType) $ f Never info -- | @LIMIT@. Limit the number of returned rows. limit :: Int64 -> SqlQuery () @@ -335,7 +347,7 @@ distinctOn exprs act = Q (W.tell mempty { sdDistinctClause = DistinctOn exprs }) -- -- @since 2.2.4 don :: SqlExpr (Value a) -> SqlExpr DistinctOn -don = EDistinctOn +don = coerce -- | A convenience function that calls both 'distinctOn' and -- 'orderBy'. In other words, @@ -361,15 +373,15 @@ distinctOnOrderBy exprs act = act where toDistinctOn :: SqlExpr OrderBy -> SqlExpr DistinctOn - toDistinctOn (EOrderBy _ f) = EDistinctOn f - toDistinctOn EOrderRandom = - error "We can't select distinct by a random order!" + toDistinctOn (ERaw m f) = ERaw m $ \p info -> + let (b, vals) = f p info + in (TLB.fromLazyText $ head $ TL.splitOn " " $ TLB.toLazyText b, vals) -- | @ORDER BY random()@ clause. -- -- @since 1.3.10 rand :: SqlExpr OrderBy -rand = EOrderRandom +rand = ERaw noMeta $ \_ _ -> ("RANDOM()", []) -- | @HAVING@. -- @@ -531,13 +543,16 @@ subSelectUnsafe :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (Va subSelectUnsafe = sub SELECT -- | Project a field of an entity. -(^.) - :: forall typ val. (PersistEntity val, PersistField typ) +(^.) :: forall typ val . (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) -(EAliasedEntityReference source base) ^. field = - EValueReference source (\_ -> aliasedEntityColumnIdent base fieldDef) +ERaw m f ^. field + | isIdField field = idFieldValue + | Just alias <- sqlExprMetaAlias m = + ERaw noMeta $ \_ info -> + f Never info <> ("." <> useIdent info (aliasedEntityColumnIdent alias fieldDef), []) + | otherwise = ERaw noMeta $ \_ info -> (dot info $ persistFieldDef field, []) where fieldDef = if isIdField field then @@ -545,48 +560,27 @@ subSelectUnsafe = sub SELECT NEL.head $ getEntityKeyFields ed else persistFieldDef field - - ed = entityDef $ getEntityVal (Proxy :: Proxy (SqlExpr (Entity val))) - -e ^. field - | isIdField field = idFieldValue - | otherwise = ERaw Never $ \info -> (dot info $ persistFieldDef field, []) - where idFieldValue = case getEntityKeyFields ed of idField :| [] -> - ERaw Never $ \info -> (dot info idField, []) + ERaw noMeta $ \_ info -> (dot info idField, []) idFields -> - ECompositeKey $ \info -> NEL.toList $ dot info <$> idFields - + let renderedFields info = dot info <$> NEL.toList idFields + in ERaw noMeta{ sqlExprMetaCompositeFields = Just renderedFields} $ + \p info -> (parensM p $ uncommas $ renderedFields info, []) ed = entityDef $ getEntityVal (Proxy :: Proxy (SqlExpr (Entity val))) dot info fieldDef = - useIdent info sourceIdent <> "." <> fieldIdent + sourceIdent info <> "." <> fieldIdent where - sourceIdent = - case e of - EEntity ident -> ident - EAliasedEntity baseI _ -> baseI - EAliasedEntityReference a b -> - error $ unwords - [ "Used (^.) with an EAliasedEntityReference." - , "Please file this as an Esqueleto bug." - , "EAliasedEntityReference", show a, show b - ] - fieldIdent = - case e of - EEntity _ -> fromDBName info (coerce $ fieldDB fieldDef) - EAliasedEntity baseI _ -> useIdent info $ aliasedEntityColumnIdent baseI fieldDef - EAliasedEntityReference a b -> - error $ unwords - [ "Used (^.) with an EAliasedEntityReference." - , "Please file this as an Esqueleto bug." - , "EAliasedEntityReference", show a, show b - ] - + sourceIdent = fmap fst $ f Never + fieldIdent + | Just baseI <- sqlExprMetaAlias m = + useIdent info $ aliasedEntityColumnIdent baseI fieldDef + | otherwise = + fromDBName info (coerce $ fieldDB fieldDef) -- | Project an SqlExpression that may be null, guarding against null cases. withNonNull @@ -599,16 +593,15 @@ withNonNull field f = do f $ veryUnsafeCoerceSqlExprValue field -- | Project a field of an entity that may be null. -(?.) - :: (PersistEntity val, PersistField typ) +(?.) :: ( PersistEntity val , PersistField typ) => SqlExpr (Maybe (Entity val)) -> EntityField val typ -> SqlExpr (Value (Maybe typ)) -EMaybe r ?. field = just (r ^. field) +ERaw m f ?. field = just (ERaw m f ^. field) -- | Lift a constant value from Haskell-land to the query. val :: PersistField typ => typ -> SqlExpr (Value typ) -val v = ERaw Never $ const ("?", [toPersistValue v]) +val v = ERaw noMeta $ \_ _ -> ("?", [toPersistValue v]) -- | @IS NULL@ comparison. -- @@ -634,27 +627,22 @@ val v = ERaw Never $ const ("?", [toPersistValue v]) isNothing :: PersistField typ => SqlExpr (Value (Maybe typ)) -> SqlExpr (Value Bool) isNothing v = case v of - ERaw p f -> - isNullExpr $ first (parensM p) . f - EAliasedValue i _ -> - isNullExpr $ aliasedValueIdentToRawSql i - EValueReference i i' -> - isNullExpr $ valueReferenceToRawSql i i' - ECompositeKey f -> - ERaw Parens $ flip (,) [] . (intersperseB " AND " . map (<> " IS NULL")) . f + ERaw m f -> + case sqlExprMetaCompositeFields m of + Just fields -> + ERaw noMeta $ \p info -> + first (parensM p) . flip (,) [] . (intersperseB " AND " . map (<> " IS NULL")) $ fields info + Nothing -> + ERaw noMeta $ \p info -> + first (parensM p) . isNullExpr $ f Never info where - isNullExpr :: (IdentInfo -> (TLB.Builder, [PersistValue])) -> SqlExpr (Value Bool) - isNullExpr g = ERaw Parens $ first ((<> " IS NULL")) . g + isNullExpr = first ((<> " IS NULL")) -- | Analogous to 'Just', promotes a value of type @typ@ into -- one of type @Maybe typ@. It should hold that @'val' . Just -- === just . 'val'@. just :: SqlExpr (Value typ) -> SqlExpr (Value (Maybe typ)) -just exprVal = case exprVal of - ERaw p f -> ERaw p f - ECompositeKey f -> ECompositeKey f - EAliasedValue i v -> EAliasedValue i (just v) - EValueReference i i' -> EValueReference i i' +just = veryUnsafeCoerceSqlExprValue -- | @NULL@ value. nothing :: SqlExpr (Value (Maybe typ)) @@ -663,23 +651,20 @@ nothing = unsafeSqlValue "NULL" -- | Join nested 'Maybe's in a 'Value' into one. This is useful when -- calling aggregate functions on nullable fields. joinV :: SqlExpr (Value (Maybe (Maybe typ))) -> SqlExpr (Value (Maybe typ)) -joinV exprMM = case exprMM of - ERaw p f -> ERaw p f - ECompositeKey f -> ECompositeKey f - EAliasedValue i v -> EAliasedValue i (joinV v) - EValueReference i i' -> EValueReference i i' +joinV = veryUnsafeCoerceSqlExprValue countHelper :: Num a => TLB.Builder -> TLB.Builder -> SqlExpr (Value typ) -> SqlExpr (Value a) countHelper open close v = case v of - ERaw _ f -> countRawSql f - EAliasedValue i _ -> countRawSql $ aliasedValueIdentToRawSql i - EValueReference i i' -> countRawSql $ valueReferenceToRawSql i i' - ECompositeKey _ -> countRows + ERaw meta f -> + if hasCompositeKeyMeta meta then + countRows + else + countRawSql (f Never) where countRawSql :: (IdentInfo -> (TLB.Builder, [PersistValue])) -> SqlExpr (Value a) - countRawSql x = ERaw Never $ first (\b -> "COUNT" <> open <> parens b <> close) . x + countRawSql x = ERaw noMeta $ \_ -> first (\b -> "COUNT" <> open <> parens b <> close) . x -- | @COUNT(*)@ value. countRows :: Num a => SqlExpr (Value a) @@ -696,19 +681,16 @@ countDistinct :: Num a => SqlExpr (Value typ) -> SqlExpr (Value a) countDistinct = countHelper "(DISTINCT " ")" not_ :: SqlExpr (Value Bool) -> SqlExpr (Value Bool) -not_ v = ERaw Never (\info -> first ("NOT " <>) $ x info) +not_ v = ERaw noMeta $ \p info -> first ("NOT " <>) $ x p info where - x info = + x p info = case v of - ERaw p f -> - let (b, vals) = f info - in (parensM p b, vals) - ECompositeKey _ -> - throw (CompositeKeyErr NotError) - EAliasedValue i _ -> - aliasedValueIdentToRawSql i info - EValueReference i i' -> - valueReferenceToRawSql i i' info + ERaw m f -> + if hasCompositeKeyMeta m then + throw (CompositeKeyErr NotError) + else + let (b, vals) = f Never info + in (parensM p b, vals) (==.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) (==.) = unsafeSqlBinOpComposite " = " " AND " @@ -905,13 +887,13 @@ castString = veryUnsafeCoerceSqlExprValue -- | Execute a subquery @SELECT@ in an SqlExpression. Returns a -- list of values. subList_select :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (ValueList a) -subList_select = EList . sub_select +subList_select query = ERaw noMeta $ \_ info -> first parens $ toRawSql SELECT info query + -- | Lift a list of constant value from Haskell-land to the query. valList :: PersistField typ => [typ] -> SqlExpr (ValueList typ) -valList [] = EEmptyList -valList vals = EList $ ERaw Parens $ const ( uncommas ("?" <$ vals) - , map toPersistValue vals ) +valList [] = ERaw noMeta $ \_ _ -> ("()", []) +valList vals = ERaw noMeta $ \p -> const (parensM p (uncommas ("?" <$ vals)), map toPersistValue vals ) -- | Same as 'just' but for 'ValueList'. Most of the time you -- won't need it, though, because you can use 'just' from @@ -919,8 +901,7 @@ valList vals = EList $ ERaw Parens $ const ( uncommas ("?" <$ vals) -- -- @since 2.2.12 justList :: SqlExpr (ValueList typ) -> SqlExpr (ValueList (Maybe typ)) -justList EEmptyList = EEmptyList -justList (EList v) = EList (just v) +justList (ERaw m f) = ERaw m f -- | @IN@ operator. For example if you want to select all @Person@s by a list -- of IDs: @@ -942,11 +923,23 @@ justList (EList v) = EList (just v) -- -- Where @personIds@ is of type @[Key Person]@. in_ :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) -v `in_` e = ifNotEmptyList e False $ unsafeSqlBinOp " IN " v (veryUnsafeCoerceSqlExprValueList e) +(ERaw _ v) `in_` (ERaw _ list) = + ERaw noMeta $ \p info -> + let (b1, vals1) = v Parens info + (b2, vals2) = list Parens info + in + if b2 == "()" then + ("FALSE", []) + else + (b1 <> " IN " <> b2, vals1 <> vals2) -- | @NOT IN@ operator. notIn :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) -v `notIn` e = ifNotEmptyList e True $ unsafeSqlBinOp " NOT IN " v (veryUnsafeCoerceSqlExprValueList e) +(ERaw _ v) `notIn` (ERaw _ list) = + ERaw noMeta $ \p info -> + let (b1, vals1) = v Parens info + (b2, vals2) = list Parens info + in (b1 <> " NOT IN " <> b2, vals1 <> vals2) -- | @EXISTS@ operator. For example: -- @@ -959,58 +952,52 @@ v `notIn` e = ifNotEmptyList e True $ unsafeSqlBinOp " NOT IN " v (veryUnsafeCo -- return person -- @ exists :: SqlQuery () -> SqlExpr (Value Bool) -exists = unsafeSqlFunction "EXISTS " . existsHelper +exists q = ERaw noMeta $ \p info -> + let ERaw _ f = existsHelper q + (b, vals) = f Never info + in ( parensM p $ "EXISTS " <> b, vals) -- | @NOT EXISTS@ operator. notExists :: SqlQuery () -> SqlExpr (Value Bool) -notExists = unsafeSqlFunction "NOT EXISTS " . existsHelper +notExists q = ERaw noMeta $ \p info -> + let ERaw _ f = existsHelper q + (b, vals) = f Never info + in ( parensM p $ "NOT EXISTS " <> b, vals) -- | @SET@ clause used on @UPDATE@s. Note that while it's not -- a type error to use this function on a @SELECT@, it will -- most certainly result in a runtime error. -set :: PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Update val)] -> SqlQuery () +set :: PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery () set ent upds = Q $ W.tell mempty { sdSetClause = map apply upds } where - apply (ESet f) = SetClause (f ent) + apply f = SetClause (f ent) -(=.) :: (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Update val) +(=.) :: (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> (SqlExpr (Entity val) -> SqlExpr Update ) field =. expr = setAux field (const expr) -(+=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Update val) +(+=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> (SqlExpr (Entity val) -> SqlExpr Update) field +=. expr = setAux field (\ent -> ent ^. field +. expr) -(-=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Update val) +(-=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> (SqlExpr (Entity val) -> SqlExpr Update) field -=. expr = setAux field (\ent -> ent ^. field -. expr) -(*=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Update val) +(*=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> (SqlExpr (Entity val) -> SqlExpr Update) field *=. expr = setAux field (\ent -> ent ^. field *. expr) -(/=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Update val) +(/=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> (SqlExpr (Entity val) -> SqlExpr Update) field /=. expr = setAux field (\ent -> ent ^. field /. expr) -- | Apply a 'PersistField' constructor to @SqlExpr Value@ arguments. (<#) :: (a -> b) -> SqlExpr (Value a) -> SqlExpr (Insertion b) -(<#) _ (ERaw _ f) = EInsert Proxy f -(<#) _ (ECompositeKey _) = throw (CompositeKeyErr ToInsertionError) -(<#) _ (EAliasedValue i _) = EInsert Proxy $ aliasedValueIdentToRawSql i -(<#) _ (EValueReference i i') = EInsert Proxy $ valueReferenceToRawSql i i' - +(<#) _ (ERaw _ f) = ERaw noMeta f -- | Apply extra @SqlExpr Value@ arguments to a 'PersistField' constructor (<&>) :: SqlExpr (Insertion (a -> b)) -> SqlExpr (Value a) -> SqlExpr (Insertion b) -(EInsert _ f) <&> v = - EInsert Proxy $ \x -> - let (fb, fv) = f x - (gb, gv) = g x - in - (fb <> ", " <> gb, fv ++ gv) - where - g = - case v of - ERaw _ f' -> f' - EAliasedValue i _ -> aliasedValueIdentToRawSql i - EValueReference i i' -> valueReferenceToRawSql i i' - ECompositeKey _ -> throw (CompositeKeyErr CombineInsertionError) +(ERaw _ f) <&> (ERaw _ g) = + ERaw noMeta $ \_ info -> + let (fb, fv) = f Never info + (gb, gv) = g Never info + in (fb <> ", " <> gb, fv ++ gv) -- | @CASE@ statement. For example: -- @@ -1300,18 +1287,15 @@ toUniqueDef uniqueConstructor = uniqueDef renderUpdates :: (BackendCompatible SqlBackend backend) => backend - -> [SqlExpr (Update val)] + -> [SqlExpr (Entity val) -> SqlExpr Update] -> (TLB.Builder, [PersistValue]) renderUpdates conn = uncommas' . concatMap renderUpdate where - mk :: SqlExpr (Value ()) -> [(TLB.Builder, [PersistValue])] - mk (ERaw _ f) = [f info] - mk (ECompositeKey _) = throw (CompositeKeyErr MakeSetError) -- FIXME - mk (EAliasedValue i _) = [aliasedValueIdentToRawSql i info] - mk (EValueReference i i') = [valueReferenceToRawSql i i' info] + mk :: SqlExpr Update -> [(TLB.Builder, [PersistValue])] + mk (ERaw _ f) = [f Never info] - renderUpdate :: SqlExpr (Update val) -> [(TLB.Builder, [PersistValue])] - renderUpdate (ESet f) = mk (f undefined) -- second parameter of f is always unused + renderUpdate :: (SqlExpr (Entity val) -> SqlExpr Update) -> [(TLB.Builder, [PersistValue])] + renderUpdate f = mk (f undefined) -- second parameter of f is always unused info = (projectBackend conn, initialIdentState) -- | Data type that represents an @INNER JOIN@ (see 'LeftOuterJoin' for an example). @@ -1390,9 +1374,6 @@ data OnClauseWithoutMatchingJoinException = instance Exception OnClauseWithoutMatchingJoinException --- | (Internal) Phantom type used to process 'from' (see 'fromStart'). -data PreprocessedFrom a - -- | Phantom type used by 'orderBy', 'asc' and 'desc'. data OrderBy @@ -1401,7 +1382,7 @@ data DistinctOn -- | Phantom type for a @SET@ operation on an entity of the given -- type (see 'set' and '(=.)'). -data Update typ +data Update -- | Phantom type used by 'insertSelect'. data Insertion a @@ -1634,7 +1615,7 @@ instance -- | (Internal) Class that implements the @JOIN@ 'from' magic -- (see 'fromStart'). class FromPreprocess a where - fromPreprocess :: SqlQuery (SqlExpr (PreprocessedFrom a)) + fromPreprocess :: SqlQuery (PreprocessedFrom a) instance (PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) @@ -1764,8 +1745,7 @@ data FromClause = FromStart Ident EntityDef | FromJoin FromClause JoinKind FromClause (Maybe (SqlExpr (Value Bool))) | OnClause (SqlExpr (Value Bool)) - | FromQuery Ident (IdentInfo -> (TLB.Builder, [PersistValue])) SubQueryType - | FromIdent Ident + | FromRaw (NeedParens -> IdentInfo -> (TLB.Builder, [PersistValue])) data CommonTableExpressionKind = RecursiveCommonTableExpression @@ -1785,8 +1765,7 @@ collectIdents fc = case fc of FromStart i _ -> Set.singleton i FromJoin lhs _ rhs _ -> collectIdents lhs <> collectIdents rhs OnClause _ -> mempty - FromQuery _ _ _ -> mempty - FromIdent _ -> mempty + FromRaw _ -> mempty instance Show FromClause where show fc = case fc of @@ -1808,10 +1787,8 @@ instance Show FromClause where ] OnClause expr -> "(OnClause " <> render' expr <> ")" - FromQuery ident _ subQueryType -> - "(FromQuery " <> show ident <> " " <> show subQueryType <> ")" - FromIdent ident -> - "(FromIdent " <> show ident <> ")" + FromRaw _ -> + "(FromRaw _)" where dummy = mkSqlBackend MkSqlBackendArgs @@ -1820,7 +1797,7 @@ instance Show FromClause where render' = T.unpack . renderExpr dummy -- | A part of a @SET@ clause. -newtype SetClause = SetClause (SqlExpr (Value ())) +newtype SetClause = SetClause (SqlExpr Update) -- | Collect 'OnClause's on 'FromJoin's. Returns the first -- unmatched 'OnClause's data on error. Returns a list without @@ -1865,14 +1842,12 @@ collectOnClauses sqlBackend = go Set.empty [] findRightmostIdent (FromStart i _) = Just i findRightmostIdent (FromJoin _ _ r _) = findRightmostIdent r findRightmostIdent (OnClause {}) = Nothing - findRightmostIdent (FromQuery _ _ _) = Nothing - findRightmostIdent (FromIdent _) = Nothing + findRightmostIdent (FromRaw _) = Nothing findLeftmostIdent (FromStart i _) = Just i findLeftmostIdent (FromJoin l _ _ _) = findLeftmostIdent l findLeftmostIdent (OnClause {}) = Nothing - findLeftmostIdent (FromQuery _ _ _) = Nothing - findLeftmostIdent (FromIdent _) = Nothing + findLeftmostIdent (FromRaw _) = Nothing tryMatch :: Set Ident @@ -2023,135 +1998,88 @@ type IdentInfo = (SqlBackend, IdentState) useIdent :: IdentInfo -> Ident -> TLB.Builder useIdent info (I ident) = fromDBName info $ DBName ident +data SqlExprMeta = SqlExprMeta + { -- A composite key. + -- + -- Persistent uses the same 'PersistList' constructor for both + -- fields which are (homogeneous) lists of values and the + -- (probably heterogeneous) values of a composite primary key. + -- + -- We need to treat composite keys as fields. For example, we + -- have to support using ==., otherwise you wouldn't be able to + -- join. OTOH, lists of values should be treated exactly the + -- same as any other scalar value. + -- + -- In particular, this is valid for persistent via rawSql for + -- an F field that is a list: + -- + -- A.F in ? -- [PersistList [foo, bar]] + -- + -- However, this is not for a composite key entity: + -- + -- A.ID = ? -- [PersistList [foo, bar]] + -- + -- The ID field doesn't exist on the DB for a composite key + -- table, it exists only on the Haskell side. Those variations + -- also don't work: + -- + -- (A.KeyA, A.KeyB) = ? -- [PersistList [foo, bar]] + -- [A.KeyA, A.KeyB] = ? -- [PersistList [foo, bar]] + -- + -- We have to generate: + -- + -- A.KeyA = ? AND A.KeyB = ? -- [foo, bar] + -- + -- Note that the PersistList had to be deconstructed into its + -- components. + -- + -- In order to disambiguate behaviors, this constructor is used + -- /only/ to represent a composite field access. It does not + -- represent a 'PersistList', not even if the 'PersistList' is + -- used in the context of a composite key. That's because it's + -- impossible, e.g., for 'val' to disambiguate between these + -- uses. + sqlExprMetaCompositeFields :: Maybe (IdentInfo -> [TLB.Builder]) + , sqlExprMetaAlias :: Maybe Ident -- Alias ident if this is an aliased value/entity + , sqlExprMetaIsReference :: Bool -- Is this SqlExpr a reference to the selected value/entity (supports subqueries) + } + +-- | Empty 'SqlExprMeta' if you are constructing an 'ERaw' probably use this +-- for your meta +noMeta :: SqlExprMeta +noMeta = SqlExprMeta + { sqlExprMetaCompositeFields = Nothing + , sqlExprMetaAlias = Nothing + , sqlExprMetaIsReference = False + } + +-- | Does this meta contain values for composite fields. +-- This field is field out for composite key values +hasCompositeKeyMeta :: SqlExprMeta -> Bool +hasCompositeKeyMeta = Maybe.isJust . sqlExprMetaCompositeFields + entityAsValue :: SqlExpr (Entity val) -> SqlExpr (Value (Entity val)) -entityAsValue eent = - case eent of - EEntity ident -> - identToRaw ident - EAliasedEntity ident _ -> - identToRaw ident - EAliasedEntityReference _ ident -> - identToRaw ident - where - identToRaw ident = - ERaw Never $ \identInfo -> - ( useIdent identInfo ident - , [] - ) +entityAsValue = coerce entityAsValueMaybe :: SqlExpr (Maybe (Entity val)) -> SqlExpr (Value (Maybe (Entity val))) -entityAsValueMaybe (EMaybe eent) = - case eent of - EEntity ident -> - identToRaw ident - EAliasedEntity ident _ -> - identToRaw ident - EAliasedEntityReference _ ident -> - identToRaw ident - where - identToRaw ident = - ERaw Never $ \identInfo -> - ( useIdent identInfo ident - , [] - ) - +entityAsValueMaybe = coerce -- | An expression on the SQL backend. -- --- There are many comments describing the constructors of this --- data type. However, Haddock doesn't like GADTs, so you'll have to read them by hitting \"Source\". -data SqlExpr a where - -- An entity, created by 'from' (cf. 'fromStart'). - EEntity :: Ident -> SqlExpr (Entity val) - -- Base Table - EAliasedEntity :: Ident -> Ident -> SqlExpr (Entity val) - -- Source Base - EAliasedEntityReference :: Ident -> Ident -> SqlExpr (Entity val) +-- Raw expression: Contains a 'SqlExprMeta' and a function for +-- building the expr. It recieves a parameter telling it whether +-- it is in a parenthesized context, and takes information about the SQL +-- connection (mainly for escaping names) and returns both an +-- string ('TLB.Builder') and a list of values to be +-- interpolated by the SQL backend. +data SqlExpr a = ERaw SqlExprMeta (NeedParens -> IdentInfo -> (TLB.Builder, [PersistValue])) - -- Just a tag stating that something is nullable. - EMaybe :: SqlExpr a -> SqlExpr (Maybe a) - - -- Raw expression: states whether parenthesis are needed - -- around this expression, and takes information about the SQL - -- connection (mainly for escaping names) and returns both an - -- string ('TLB.Builder') and a list of values to be - -- interpolated by the SQL backend. - ERaw :: NeedParens -> (IdentInfo -> (TLB.Builder, [PersistValue])) -> SqlExpr (Value a) - - - -- A raw expression with an alias - EAliasedValue :: Ident -> SqlExpr (Value a) -> SqlExpr (Value a) - - -- A reference to an aliased field in a table or subquery - EValueReference :: Ident -> (IdentInfo -> Ident) -> SqlExpr (Value a) - - -- A composite key. - -- - -- Persistent uses the same 'PersistList' constructor for both - -- fields which are (homogeneous) lists of values and the - -- (probably heterogeneous) values of a composite primary key. - -- - -- We need to treat composite keys as fields. For example, we - -- have to support using ==., otherwise you wouldn't be able to - -- join. OTOH, lists of values should be treated exactly the - -- same as any other scalar value. - -- - -- In particular, this is valid for persistent via rawSql for - -- an F field that is a list: - -- - -- A.F in ? -- [PersistList [foo, bar]] - -- - -- However, this is not for a composite key entity: - -- - -- A.ID = ? -- [PersistList [foo, bar]] - -- - -- The ID field doesn't exist on the DB for a composite key - -- table, it exists only on the Haskell side. Those variations - -- also don't work: - -- - -- (A.KeyA, A.KeyB) = ? -- [PersistList [foo, bar]] - -- [A.KeyA, A.KeyB] = ? -- [PersistList [foo, bar]] - -- - -- We have to generate: - -- - -- A.KeyA = ? AND A.KeyB = ? -- [foo, bar] - -- - -- Note that the PersistList had to be deconstructed into its - -- components. - -- - -- In order to disambiguate behaviors, this constructor is used - -- /only/ to represent a composite field access. It does not - -- represent a 'PersistList', not even if the 'PersistList' is - -- used in the context of a composite key. That's because it's - -- impossible, e.g., for 'val' to disambiguate between these - -- uses. - ECompositeKey :: (IdentInfo -> [TLB.Builder]) -> SqlExpr (Value a) - - -- 'EList' and 'EEmptyList' are used by list operators. - EList :: SqlExpr (Value a) -> SqlExpr (ValueList a) - EEmptyList :: SqlExpr (ValueList a) - - -- A 'SqlExpr' accepted only by 'orderBy'. - EOrderBy :: OrderByType -> SqlExpr (Value a) -> SqlExpr OrderBy - - EOrderRandom :: SqlExpr OrderBy - - -- A 'SqlExpr' accepted only by 'distinctOn'. - EDistinctOn :: SqlExpr (Value a) -> SqlExpr DistinctOn - - -- A 'SqlExpr' accepted only by 'set'. - ESet :: (SqlExpr (Entity val) -> SqlExpr (Value ())) -> SqlExpr (Update val) - - -- An internal 'SqlExpr' used by the 'from' hack. - EPreprocessedFrom :: a -> FromClause -> SqlExpr (PreprocessedFrom a) - - -- Used by 'insertSelect'. - EInsert :: Proxy a -> (IdentInfo -> (TLB.Builder, [PersistValue])) -> SqlExpr (Insertion a) - EInsertFinal :: PersistEntity a => SqlExpr (Insertion a) -> SqlExpr InsertFinal +-- | Data type to support from hack +data PreprocessedFrom a = PreprocessedFrom a FromClause -- | Phantom type used to mark a @INSERT INTO@ query. data InsertFinal @@ -2178,13 +2106,14 @@ setAux :: (PersistEntity val, PersistField typ) => EntityField val typ -> (SqlExpr (Entity val) -> SqlExpr (Value typ)) - -> SqlExpr (Update val) -setAux field mkVal = ESet $ \ent -> unsafeSqlBinOp " = " name (mkVal ent) - where - name = ERaw Never $ \info -> (fieldName info field, mempty) + -> (SqlExpr (Entity val) -> SqlExpr Update) +setAux field value = \ent -> ERaw noMeta $ \_ info -> + let ERaw _ valueF = value ent + (valueToSet, valueVals) = valueF Parens info + in (fieldName info field <> " = " <> valueToSet, valueVals) sub :: PersistField a => Mode -> SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value a) -sub mode query = ERaw Parens $ \info -> toRawSql mode info query +sub mode query = ERaw noMeta $ \_ info -> first parens $ toRawSql mode info query fromDBName :: IdentInfo -> DBName -> TLB.Builder fromDBName (conn, _) = TLB.fromText . flip getEscapedRawName conn . unDBName @@ -2192,47 +2121,34 @@ fromDBName (conn, _) = TLB.fromText . flip getEscapedRawName conn . unDBName existsHelper :: SqlQuery () -> SqlExpr (Value Bool) existsHelper = sub SELECT . (>> return true) where - true :: SqlExpr (Value Bool) + true :: SqlExpr (Value Bool) true = val True -ifNotEmptyList :: SqlExpr (ValueList a) -> Bool -> SqlExpr (Value Bool) -> SqlExpr (Value Bool) -ifNotEmptyList EEmptyList b _ = val b -ifNotEmptyList (EList _) _ x = x - -- | (Internal) Create a case statement. -- -- Since: 2.1.1 unsafeSqlCase :: PersistField a => [(SqlExpr (Value Bool), SqlExpr (Value a))] -> SqlExpr (Value a) -> SqlExpr (Value a) -unsafeSqlCase when v = ERaw Never buildCase +unsafeSqlCase when v = ERaw noMeta buildCase where - buildCase :: IdentInfo -> (TLB.Builder, [PersistValue]) - buildCase info = - let (elseText, elseVals) = valueToRawSqlParens SqlCaseError v info - (whenText, whenVals) = mapWhen when info + buildCase :: NeedParens -> IdentInfo -> (TLB.Builder, [PersistValue]) + buildCase p info = + let (elseText, elseVals) = valueToSql v Parens info + (whenText, whenVals) = mapWhen when Parens info in ( "CASE" <> whenText <> " ELSE " <> elseText <> " END", whenVals <> elseVals) - mapWhen :: [(SqlExpr (Value Bool), SqlExpr (Value a))] -> IdentInfo -> (TLB.Builder, [PersistValue]) - mapWhen [] _ = throw (UnexpectedCaseErr UnsafeSqlCaseError) - mapWhen when' info = foldl (foldHelp info) (mempty, mempty) when' + mapWhen :: [(SqlExpr (Value Bool), SqlExpr (Value a))] -> NeedParens -> IdentInfo -> (TLB.Builder, [PersistValue]) + mapWhen [] _ _ = throw (UnexpectedCaseErr UnsafeSqlCaseError) + mapWhen when' p info = foldl (foldHelp p info) (mempty, mempty) when' - foldHelp :: IdentInfo -> (TLB.Builder, [PersistValue]) -> (SqlExpr (Value Bool), SqlExpr (Value a)) -> (TLB.Builder, [PersistValue]) - foldHelp _ _ (ECompositeKey _, _) = throw (CompositeKeyErr FoldHelpError) - foldHelp _ _ (_, ECompositeKey _) = throw (CompositeKeyErr FoldHelpError) - foldHelp info (b0, vals0) (v1, v2) = - let (b1, vals1) = valueToRawSqlParens SqlCaseError v1 info - (b2, vals2) = valueToRawSqlParens SqlCaseError v2 info + + foldHelp :: NeedParens -> IdentInfo -> (TLB.Builder, [PersistValue]) -> (SqlExpr (Value Bool), SqlExpr (Value a)) -> (TLB.Builder, [PersistValue]) + foldHelp p info (b0, vals0) (v1, v2) = + let (b1, vals1) = valueToSql v1 p info + (b2, vals2) = valueToSql v2 p info in ( b0 <> " WHEN " <> b1 <> " THEN " <> b2, vals0 <> vals1 <> vals2 ) --- | (Internal) Convert a value to a raw SQL builder, preserving parens around --- 'ERaw' SQL expressions. This is useful for turning values into function or --- operator arguments. --- --- Since: 3.4.0.2 -valueToRawSqlParens :: UnexpectedValueError -> SqlExpr (Value a) -> IdentInfo -> (TLB.Builder, [PersistValue]) -valueToRawSqlParens _ (ERaw p f) = (first (parensM p)) . f -valueToRawSqlParens e (ECompositeKey _) = throw (CompositeKeyErr e) -valueToRawSqlParens _ (EAliasedValue i _) = aliasedValueIdentToRawSql i -valueToRawSqlParens _ (EValueReference i i') = valueReferenceToRawSql i i' + valueToSql :: SqlExpr (Value a) -> NeedParens -> IdentInfo -> (TLB.Builder, [PersistValue]) + valueToSql (ERaw _ f) p = f p -- | (Internal) Create a custom binary operator. You /should/ -- /not/ use this function directly since its type is very @@ -2247,32 +2163,31 @@ valueToRawSqlParens _ (EValueReference i i') = valueReferenceToRawSql i i' -- In the example above, we constraint the arguments to be of the -- same type and constraint the result to be a boolean value. unsafeSqlBinOp :: TLB.Builder -> SqlExpr (Value a) -> SqlExpr (Value b) -> SqlExpr (Value c) -unsafeSqlBinOp op (ERaw p1 f1) (ERaw p2 f2) = ERaw Parens f +unsafeSqlBinOp op (ERaw m1 f1) (ERaw m2 f2) + | not (hasCompositeKeyMeta m1 || hasCompositeKeyMeta m2) = ERaw noMeta f where - f info = - let (b1, vals1) = f1 info - (b2, vals2) = f2 info + f p info = + let (b1, vals1) = f1 Parens info + (b2, vals2) = f2 Parens info in - ( parensM p1 b1 <> op <> parensM p2 b2 + ( parensM p (b1 <> op <> b2) , vals1 <> vals2 ) unsafeSqlBinOp op a b = unsafeSqlBinOp op (construct a) (construct b) where construct :: SqlExpr (Value a) -> SqlExpr (Value a) - construct (ERaw p f) = - ERaw (if p == Never then Parens else Never) $ \info -> - let (b1, vals) = f info - build ("?", [PersistList vals']) = - (uncommas $ replicate (length vals') "?", vals') - build expr = expr - in - build (parensM p b1, vals) - construct (ECompositeKey f) = - ERaw Parens $ \info -> (uncommas $ f info, mempty) - construct (EAliasedValue i _) = - ERaw Never $ aliasedValueIdentToRawSql i - construct (EValueReference i i') = - ERaw Never $ valueReferenceToRawSql i i' + construct (ERaw m f) = + case sqlExprMetaCompositeFields m of + Just fields -> + ERaw noMeta $ \_ info -> (parens $ uncommas $ fields info, mempty) + Nothing -> + ERaw noMeta $ \p info -> + let (b1, vals) = f (if p == Never then Parens else Never) info + build ("?", [PersistList vals']) = + (uncommas $ replicate (length vals') "?", vals') + build expr = expr + in + first (parensM p) $ build (b1, vals) {-# INLINE unsafeSqlBinOp #-} -- | Similar to 'unsafeSqlBinOp', but may also be applied to @@ -2300,18 +2215,16 @@ unsafeSqlBinOp op a b = unsafeSqlBinOp op (construct a) (construct b) -- no placeholders and split it on the commas. unsafeSqlBinOpComposite :: TLB.Builder -> TLB.Builder -> SqlExpr (Value a) -> SqlExpr (Value b) -> SqlExpr (Value c) unsafeSqlBinOpComposite op sep a b - | isCompositeKey a || isCompositeKey b = ERaw Parens $ compose (listify a) (listify b) + | isCompositeKey a || isCompositeKey b = ERaw noMeta $ const $ compose (listify a) (listify b) | otherwise = unsafeSqlBinOp op a b where isCompositeKey :: SqlExpr (Value x) -> Bool - isCompositeKey (ECompositeKey _) = True - isCompositeKey _ = False + isCompositeKey (ERaw m _) = hasCompositeKeyMeta m listify :: SqlExpr (Value x) -> IdentInfo -> ([TLB.Builder], [PersistValue]) - listify (ECompositeKey f) = flip (,) [] . f - listify (ERaw _ f) = deconstruct . f - listify (EAliasedValue i _) = deconstruct . (aliasedValueIdentToRawSql i) - listify (EValueReference i i') = deconstruct . (valueReferenceToRawSql i i') + listify (ERaw m f) + | Just f <- sqlExprMetaCompositeFields m = flip (,) [] . f + | otherwise = deconstruct . f Parens deconstruct :: (TLB.Builder, [PersistValue]) -> ([TLB.Builder], [PersistValue]) deconstruct ("?", [PersistList vals]) = (replicate (length vals) "?", vals) @@ -2328,19 +2241,19 @@ unsafeSqlBinOpComposite op sep a b bc = intersperseB sep [x <> op <> y | (x, y) <- zip b1 b2] vc = v1 <> v2 + -- | (Internal) A raw SQL value. The same warning from -- 'unsafeSqlBinOp' applies to this function as well. unsafeSqlValue :: TLB.Builder -> SqlExpr (Value a) -unsafeSqlValue v = ERaw Never $ const (v, mempty) +unsafeSqlValue v = ERaw noMeta $ \_ _ -> (v, mempty) {-# INLINE unsafeSqlValue #-} +unsafeSqlEntity :: PersistEntity ent => Ident -> SqlExpr (Entity ent) +unsafeSqlEntity ident = ERaw noMeta $ \_ info -> + (useIdent info ident, []) + valueToFunctionArg :: IdentInfo -> SqlExpr (Value a) -> (TLB.Builder, [PersistValue]) -valueToFunctionArg info v = - case v of - ERaw _ f -> f info - EAliasedValue i _ -> aliasedValueIdentToRawSql i info - EValueReference i i' -> valueReferenceToRawSql i i' info - ECompositeKey _ -> throw (CompositeKeyErr SqlFunctionError) +valueToFunctionArg info (ERaw _ f) = f Never info -- | (Internal) A raw SQL function. Once again, the same warning -- from 'unsafeSqlBinOp' applies to this function as well. @@ -2348,7 +2261,7 @@ unsafeSqlFunction :: UnsafeSqlFunctionArgument a => TLB.Builder -> a -> SqlExpr (Value b) unsafeSqlFunction name arg = - ERaw Never $ \info -> + ERaw noMeta $ \p info -> let (argsTLB, argsVals) = uncommas' $ map (valueToFunctionArg info) $ toArgList arg in @@ -2362,7 +2275,7 @@ unsafeSqlExtractSubField :: UnsafeSqlFunctionArgument a => TLB.Builder -> a -> SqlExpr (Value b) unsafeSqlExtractSubField subField arg = - ERaw Never $ \info -> + ERaw noMeta $ \_ info -> let (argsTLB, argsVals) = uncommas' $ map (valueToFunctionArg info) $ toArgList arg in @@ -2374,25 +2287,16 @@ unsafeSqlFunctionParens :: UnsafeSqlFunctionArgument a => TLB.Builder -> a -> SqlExpr (Value b) unsafeSqlFunctionParens name arg = - ERaw Never $ \info -> - let (argsTLB, argsVals) = - uncommas' $ map (\v -> valueToRawSqlParens SqlFunctionError v info) $ toArgList arg - in - (name <> parens argsTLB, argsVals) + ERaw noMeta $ \p info -> + let valueToFunctionArgParens (ERaw _ f) = f Never info + (argsTLB, argsVals) = + uncommas' $ map valueToFunctionArgParens $ toArgList arg + in (name <> parens argsTLB, argsVals) -- | (Internal) An explicit SQL type cast using CAST(value as type). -- See 'unsafeSqlBinOp' for warnings. unsafeSqlCastAs :: T.Text -> SqlExpr (Value a) -> SqlExpr (Value b) -unsafeSqlCastAs t v = ERaw Never ((first (\value -> "CAST" <> parens (value <> " AS " <> TLB.fromText t))) . valueToText) - where - valueToText info = - case v of - (ERaw p f) -> - let (b, vals) = f info - in (parensM p b, vals) - EAliasedValue i _ -> aliasedValueIdentToRawSql i info - EValueReference i i' -> valueReferenceToRawSql i i' info - ECompositeKey _ -> throw (CompositeKeyErr SqlCastAsError) +unsafeSqlCastAs t (ERaw _ f) = ERaw noMeta $ \_ -> ((first (\value -> "CAST" <> parens (value <> " AS " <> TLB.fromText t))) . f Never) -- | (Internal) This class allows 'unsafeSqlFunction' to work with different -- numbers of arguments; specifically it allows providing arguments to a sql @@ -2523,17 +2427,13 @@ instance ( UnsafeSqlFunctionArgument a -- 'SqlExpr (Value b)'. You should /not/ use this function -- unless you know what you're doing! veryUnsafeCoerceSqlExprValue :: SqlExpr (Value a) -> SqlExpr (Value b) -veryUnsafeCoerceSqlExprValue (ERaw p f) = ERaw p f -veryUnsafeCoerceSqlExprValue (ECompositeKey f) = ECompositeKey f -veryUnsafeCoerceSqlExprValue (EAliasedValue i v) = EAliasedValue i (veryUnsafeCoerceSqlExprValue v) -veryUnsafeCoerceSqlExprValue (EValueReference i i') = EValueReference i i' +veryUnsafeCoerceSqlExprValue = coerce -- | (Internal) Coerce a value's type from 'SqlExpr (ValueList -- a)' to 'SqlExpr (Value a)'. Does not work with empty lists. veryUnsafeCoerceSqlExprValueList :: SqlExpr (ValueList a) -> SqlExpr (Value a) -veryUnsafeCoerceSqlExprValueList (EList v) = v -veryUnsafeCoerceSqlExprValueList EEmptyList = throw (UnexpectedCaseErr EmptySqlExprValueList) +veryUnsafeCoerceSqlExprValueList = coerce ---------------------------------------------------------------------- @@ -2903,7 +2803,7 @@ makeSelect info mode_ distinctClause ret = process mode_ first (("SELECT DISTINCT ON (" <>) . (<> ") ")) $ uncommas' (processExpr <$> exprs) where - processExpr (EDistinctOn f) = materializeExpr info f + processExpr e = materializeExpr info (coerce e :: SqlExpr (Value a)) withCols v = v <> sqlSelectCols info ret plain v = (v, []) @@ -2933,18 +2833,7 @@ makeFrom info mode fs = ret , maybe mempty makeOnClause monClause ] mk _ (OnClause _) = throw (UnexpectedCaseErr MakeFromError) - mk _ (FromQuery ident f subqueryType) = - let (queryText, queryVals) = f info - lateralKeyword = - case subqueryType of - NormalSubQuery -> "" - LateralSubQuery -> "LATERAL " - in - ( lateralKeyword <> (parens queryText) <> " AS " <> useIdent info ident - , queryVals - ) - mk _ (FromIdent ident) = - (useIdent info ident, mempty) + mk paren (FromRaw f) = f paren info base ident@(I identText) def = let db@(DBName dbText) = coerce $ getEntityDBName def @@ -2961,38 +2850,22 @@ makeFrom info mode fs = ret fromKind RightOuterJoinKind = " RIGHT OUTER JOIN " fromKind FullOuterJoinKind = " FULL OUTER JOIN " - makeOnClause (ERaw _ f) = first (" ON " <>) (f info) - makeOnClause (ECompositeKey _) = throw (CompositeKeyErr MakeOnClauseError) - makeOnClause (EAliasedValue _ _) = throw (AliasedValueErr MakeOnClauseError) - makeOnClause (EValueReference _ _) = throw (AliasedValueErr MakeOnClauseError) + makeOnClause (ERaw _ f) = first (" ON " <>) (f Never info) mkExc :: SqlExpr (Value Bool) -> OnClauseWithoutMatchingJoinException mkExc (ERaw _ f) = OnClauseWithoutMatchingJoinException $ - TL.unpack $ TLB.toLazyText $ fst (f info) - mkExc (ECompositeKey _) = throw (CompositeKeyErr MakeExcError) - mkExc (EAliasedValue _ _) = throw (AliasedValueErr MakeExcError) - mkExc (EValueReference _ _) = throw (AliasedValueErr MakeExcError) + TL.unpack $ TLB.toLazyText $ fst (f Never info) makeSet :: IdentInfo -> [SetClause] -> (TLB.Builder, [PersistValue]) makeSet _ [] = mempty makeSet info os = first ("\nSET " <>) . uncommas' $ concatMap mk os where - mk (SetClause (ERaw _ f)) = [f info] - mk (SetClause (ECompositeKey _)) = throw (CompositeKeyErr MakeSetError) -- FIXME - mk (SetClause (EAliasedValue i _)) = [aliasedValueIdentToRawSql i info] - mk (SetClause (EValueReference i i')) = [valueReferenceToRawSql i i' info] + mk (SetClause (ERaw _ f)) = [f Never info] makeWhere :: IdentInfo -> WhereClause -> (TLB.Builder, [PersistValue]) -makeWhere _ NoWhere = mempty -makeWhere info (Where v) = first ("\nWHERE " <>) $ x info - where - x = - case v of - ERaw _ f -> f - EAliasedValue i _ -> aliasedValueIdentToRawSql i - EValueReference i i' -> valueReferenceToRawSql i i' - ECompositeKey _ -> throw (CompositeKeyErr MakeWhereError) +makeWhere _ NoWhere = mempty +makeWhere info (Where (ERaw _ f)) = first ("\nWHERE " <>) $ f Never info makeGroupBy :: IdentInfo -> GroupByClause -> (TLB.Builder, [PersistValue]) makeGroupBy _ (GroupBy []) = (mempty, []) @@ -3002,21 +2875,11 @@ makeGroupBy info (GroupBy fields) = first ("\nGROUP BY " <>) build build = uncommas' $ map match fields match :: SomeValue -> (TLB.Builder, [PersistValue]) - match (SomeValue (ERaw _ f)) = f info - match (SomeValue (ECompositeKey f)) = (uncommas $ f info, mempty) - match (SomeValue (EAliasedValue i _)) = aliasedValueIdentToRawSql i info - match (SomeValue (EValueReference i i')) = valueReferenceToRawSql i i' info + match (SomeValue (ERaw _ f)) = f Never info makeHaving :: IdentInfo -> WhereClause -> (TLB.Builder, [PersistValue]) makeHaving _ NoWhere = mempty -makeHaving info (Where v) = first ("\nHAVING " <>) $ x info - where - x = - case v of - ERaw _ f -> f - EAliasedValue i _ -> aliasedValueIdentToRawSql i - EValueReference i i' -> valueReferenceToRawSql i i' - ECompositeKey _ -> throw (CompositeKeyErr MakeHavingError) +makeHaving info (Where (ERaw _ f)) = first ("\nHAVING " <>) $ f Never info -- makeHaving, makeWhere and makeOrderBy makeOrderByNoNewline @@ -3025,19 +2888,7 @@ makeOrderByNoNewline _ [] = mempty makeOrderByNoNewline info os = first ("ORDER BY " <>) . uncommas' $ concatMap mk os where mk :: OrderByClause -> [(TLB.Builder, [PersistValue])] - mk (EOrderBy t (ECompositeKey f)) = - let fs = f info - vals = repeat [] - in zip (map (<> orderByType t) fs) vals - mk (EOrderBy t v) = - let x = - case v of - ERaw p f -> (first (parensM p)) . f - EAliasedValue i _ -> aliasedValueIdentToRawSql i - EValueReference i i' -> valueReferenceToRawSql i i' - ECompositeKey _ -> undefined -- defined above - in [ first (<> orderByType t) $ x info ] - mk EOrderRandom = [first (<> "RANDOM()") mempty] + mk (ERaw _ f) = [f Never info] orderByType ASC = " ASC" orderByType DESC = " DESC" @@ -3048,8 +2899,6 @@ makeOrderBy info is = let (tlb, vals) = makeOrderByNoNewline info is in ("\n" <> tlb, vals) -{-# DEPRECATED EOrderRandom "Since 2.6.0: `rand` ordering function is not uniform across all databases! To avoid accidental partiality it will be removed in the next major version." #-} - makeLimit :: IdentInfo -> LimitClause -> [OrderByClause] -> (TLB.Builder, [PersistValue]) makeLimit (conn, _) (Limit ml mo) orderByClauses = let limitRaw = getConnLimitOffset (v ml, v mo) "\n" conn @@ -3067,13 +2916,6 @@ makeLocking = flip (,) [] . maybe mempty toTLB . Monoid.getLast parens :: TLB.Builder -> TLB.Builder parens b = "(" <> (b <> ")") -aliasedValueIdentToRawSql :: Ident -> IdentInfo -> (TLB.Builder, [PersistValue]) -aliasedValueIdentToRawSql i info = (useIdent info i, mempty) - -valueReferenceToRawSql :: Ident -> (IdentInfo -> Ident) -> IdentInfo -> (TLB.Builder, [PersistValue]) -valueReferenceToRawSql sourceIdent columnIdentF info = - (useIdent info sourceIdent <> "." <> useIdent info (columnIdentF info), mempty) - aliasedEntityColumnIdent :: Ident -> FieldDef -> Ident aliasedEntityColumnIdent (I baseIdent) field = I (baseIdent <> "_" <> (unDBName $ coerce $ fieldDB field)) @@ -3106,18 +2948,22 @@ class SqlSelect a r | a -> r, r -> a where -- | @INSERT INTO@ hack. -instance SqlSelect (SqlExpr InsertFinal) InsertFinal where - sqlInsertInto info (EInsertFinal (EInsert p _)) = +instance PersistEntity e => SqlSelect (SqlExpr (Insertion e)) (Insertion e) where + sqlInsertInto info e = let fields = uncommas $ map (fromDBName info . coerce . fieldDB) $ getEntityFields $ - entityDef p + entityDef (proxy e) + + proxy :: SqlExpr (Insertion a) -> Proxy a + proxy = const Proxy + table = - fromDBName info . DBName . coerce . getEntityDBName . entityDef $ p + fromDBName info . DBName . coerce . getEntityDBName . entityDef . proxy in - ("INSERT INTO " <> table <> parens fields <> "\n", []) - sqlSelectCols info (EInsertFinal (EInsert _ f)) = f info + ("INSERT INTO " <> table e <> parens fields <> "\n", []) + sqlSelectCols info (ERaw _ f) = f Never info sqlSelectColCount = const 0 sqlSelectProcessRow = const (Right (throw (UnexpectedCaseErr InsertionFinalError))) @@ -3143,39 +2989,38 @@ unescapedColumnNames ent = -- | You may return an 'Entity' from a 'select' query. instance PersistEntity a => SqlSelect (SqlExpr (Entity a)) (Entity a) where - sqlSelectCols info expr@(EEntity ident) = ret - where - process ed = - uncommas - $ map ((name <>) . TLB.fromText) - $ NEL.toList - $ keyAndEntityColumnNames ed (fst info) - -- 'name' is the biggest difference between 'RawSql' and - -- 'SqlSelect'. We automatically create names for tables - -- (since it's not the user who's writing the FROM - -- clause), while 'rawSql' assumes that it's just the - -- name of the table (which doesn't allow self-joins, for - -- example). - name = useIdent info ident <> "." - ret = let ed = entityDef $ getEntityVal $ return expr - in (process ed, mempty) - sqlSelectCols info expr@(EAliasedEntity aliasIdent tableIdent) = ret - where - process ed = uncommas $ - map ((name <>) . aliasName) $ - unescapedColumnNames ed - aliasName columnName = (fromDBName info columnName) <> " AS " <> aliasedColumnName aliasIdent info (unDBName columnName) - name = useIdent info tableIdent <> "." - ret = let ed = entityDef $ getEntityVal $ return expr - in (process ed, mempty) - sqlSelectCols info expr@(EAliasedEntityReference sourceIdent baseIdent) = ret - where - process ed = uncommas $ - map ((name <>) . aliasedColumnName baseIdent info . unDBName) $ - unescapedColumnNames ed - name = useIdent info sourceIdent <> "." - ret = let ed = entityDef $ getEntityVal $ return expr - in (process ed, mempty) + sqlSelectCols info expr@(ERaw m f) + | Just baseIdent <- sqlExprMetaAlias m, False <- sqlExprMetaIsReference m = + let process ed = uncommas $ + map ((name <>) . aliasName) $ + unescapedColumnNames ed + aliasName columnName = (fromDBName info columnName) <> " AS " <> aliasedColumnName baseIdent info (unDBName columnName) + name = fst (f Never info) <> "." + ed = entityDef $ getEntityVal $ return expr + in (process ed, mempty) + | Just baseIdent <- sqlExprMetaAlias m, True <- sqlExprMetaIsReference m = + let process ed = uncommas $ + map ((name <>) . aliasedColumnName baseIdent info . unDBName) $ + unescapedColumnNames ed + name = fst (f Never info) <> "." + ed = entityDef $ getEntityVal $ return expr + in (process ed, mempty) + | otherwise = + let process ed = + uncommas + $ map ((name <>) . TLB.fromText) + $ NEL.toList + $ keyAndEntityColumnNames ed (fst info) + -- 'name' is the biggest difference between 'RawSql' and + -- 'SqlSelect'. We automatically create names for tables + -- (since it's not the user who's writing the FROM + -- clause), while 'rawSql' assumes that it's just the + -- name of the table (which doesn't allow self-joins, for + -- example). + name = fst (f Never info) <> "." + ed = entityDef $ getEntityVal $ return expr + in (process ed, mempty) + sqlSelectColCount = entityColumnCount . entityDef . getEntityVal sqlSelectProcessRow = parseEntityValues ed where @@ -3186,7 +3031,7 @@ getEntityVal = const Proxy -- | You may return a possibly-@NULL@ 'Entity' from a 'select' query. instance PersistEntity a => SqlSelect (SqlExpr (Maybe (Entity a))) (Maybe (Entity a)) where - sqlSelectCols info (EMaybe ent) = sqlSelectCols info ent + sqlSelectCols info e = sqlSelectCols info (coerce e :: SqlExpr (Entity a)) sqlSelectColCount = sqlSelectColCount . fromEMaybe where fromEMaybe :: Proxy (SqlExpr (Maybe e)) -> Proxy (SqlExpr e) @@ -3206,17 +3051,12 @@ instance PersistField a => SqlSelect (SqlExpr (Value a)) (Value a) where -- | Materialize a @SqlExpr (Value a)@. materializeExpr :: IdentInfo -> SqlExpr (Value a) -> (TLB.Builder, [PersistValue]) -materializeExpr info (ERaw p f) = - let (b, vals) = f info - in (parensM p b, vals) -materializeExpr info (ECompositeKey f) = - let bs = f info - in (uncommas $ map (parensM Parens) bs, []) -materializeExpr info (EAliasedValue ident x) = - let (b, vals) = materializeExpr info x - in (b <> " AS " <> (useIdent info ident), vals) -materializeExpr info (EValueReference sourceIdent columnIdent) = - valueReferenceToRawSql sourceIdent columnIdent info +materializeExpr info (ERaw m f) + | Just fields <- sqlExprMetaCompositeFields m = (uncommas $ fmap parens $ fields info, []) + | Just alias <- sqlExprMetaAlias m + , not (sqlExprMetaIsReference m) = first (<> " AS " <> useIdent info alias) (f Parens info) + | otherwise = f Parens info + -- | You may return tuples (up to 16-tuples) and tuples of tuples -- from a 'select' query. @@ -3731,7 +3571,7 @@ insertSelectCount :: (MonadIO m, PersistEntity a) => SqlQuery (SqlExpr (Insertion a)) -> SqlWriteT m Int64 -insertSelectCount = rawEsqueleto INSERT_INTO . fmap EInsertFinal +insertSelectCount = rawEsqueleto INSERT_INTO -- | Renders an expression into 'Text'. Only useful for creating a textual -- representation of the clauses passed to an "On" clause. @@ -3739,20 +3579,8 @@ insertSelectCount = rawEsqueleto INSERT_INTO . fmap EInsertFinal -- @since 3.2.0 renderExpr :: SqlBackend -> SqlExpr (Value Bool) -> T.Text renderExpr sqlBackend e = case e of - ERaw _ mkBuilderValues -> do - let (builder, _) = mkBuilderValues (sqlBackend, initialIdentState) - in (builderToText builder) - ECompositeKey mkInfo -> - throw - . RenderExprUnexpectedECompositeKey - . builderToText - . mconcat - . mkInfo - $ (sqlBackend, initialIdentState) - EAliasedValue i _ -> - builderToText $ useIdent (sqlBackend, initialIdentState) i - EValueReference i i' -> - let (builder, _) = valueReferenceToRawSql i i' (sqlBackend, initialIdentState) + ERaw _ mkBuilderValues -> + let (builder, _) = mkBuilderValues Never (sqlBackend, initialIdentState) in (builderToText builder) -- | An exception thrown by 'RenderExpr' - it's not designed to handle composite diff --git a/src/Database/Esqueleto/Internal/Sql.hs b/src/Database/Esqueleto/Internal/Sql.hs index 3b92975..2af0009 100644 --- a/src/Database/Esqueleto/Internal/Sql.hs +++ b/src/Database/Esqueleto/Internal/Sql.hs @@ -37,8 +37,8 @@ module Database.Esqueleto.Internal.Sql -- * The guts , unsafeSqlCase , unsafeSqlBinOp - , unsafeSqlBinOpComposite , unsafeSqlValue + , unsafeSqlEntity , unsafeSqlCastAs , unsafeSqlFunction , unsafeSqlExtractSubField diff --git a/src/Database/Esqueleto/PostgreSQL.hs b/src/Database/Esqueleto/PostgreSQL.hs index 94e4a30..ffecb3c 100644 --- a/src/Database/Esqueleto/PostgreSQL.hs +++ b/src/Database/Esqueleto/PostgreSQL.hs @@ -85,18 +85,18 @@ unsafeSqlAggregateFunction -> a -> [OrderByClause] -> SqlExpr (Value b) -unsafeSqlAggregateFunction name mode args orderByClauses = ERaw Never $ \info -> +unsafeSqlAggregateFunction name mode args orderByClauses = ERaw noMeta $ \_ info -> let (orderTLB, orderVals) = makeOrderByNoNewline info orderByClauses -- Don't add a space if we don't have order by clauses orderTLBSpace = case orderByClauses of - [] -> "" + [] -> "" (_:_) -> " " (argsTLB, argsVals) = - uncommas' $ map (\v -> valueToRawSqlParens SqlFunctionError v info) $ toArgList args + uncommas' $ map (\(ERaw _ f) -> f Never info) $ toArgList args aggMode = case mode of - AggModeAll -> "" + AggModeAll -> "" -- ALL is the default, so we don't need to -- specify it AggModeDistinct -> "DISTINCT " @@ -184,7 +184,7 @@ upsert ) => record -- ^ new record to insert - -> [SqlExpr (Update record)] + -> [SqlExpr (Entity record) -> SqlExpr Update] -- ^ updates to perform if the record already exists -> R.ReaderT SqlBackend m (Entity record) -- ^ the record in the database after the operation @@ -202,7 +202,7 @@ upsertBy -- ^ uniqueness constraint to find by -> record -- ^ new record to insert - -> [SqlExpr (Update record)] + -> [SqlExpr (Entity record) -> SqlExpr Update] -- ^ updates to perform if the record already exists -> R.ReaderT SqlBackend m (Entity record) -- ^ the record in the database after the operation @@ -278,7 +278,7 @@ insertSelectWithConflict -- a unique "MyUnique 0", "MyUnique undefined" would work as well. -> SqlQuery (SqlExpr (Insertion val)) -- ^ Insert query. - -> (SqlExpr (Entity val) -> SqlExpr (Entity val) -> [SqlExpr (Update val)]) + -> (SqlExpr (Entity val) -> SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update]) -- ^ A list of updates to be applied in case of the constraint being -- violated. The expression takes the current and excluded value to produce -- the updates. @@ -294,22 +294,22 @@ insertSelectWithConflictCount . (FinalResult a, KnowResult a ~ Unique val, MonadIO m, PersistEntity val) => a -> SqlQuery (SqlExpr (Insertion val)) - -> (SqlExpr (Entity val) -> SqlExpr (Entity val) -> [SqlExpr (Update val)]) + -> (SqlExpr (Entity val) -> SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update]) -> SqlWriteT m Int64 insertSelectWithConflictCount unique query conflictQuery = do conn <- R.ask uncurry rawExecuteCount $ combine - (toRawSql INSERT_INTO (conn, initialIdentState) (fmap EInsertFinal query)) + (toRawSql INSERT_INTO (conn, initialIdentState) query) (conflict conn) where proxy :: Proxy val proxy = Proxy updates = conflictQuery entCurrent entExcluded combine (tlb1,vals1) (tlb2,vals2) = (builderToText (tlb1 `mappend` tlb2), vals1 ++ vals2) - entExcluded = EEntity $ I "excluded" + entExcluded = unsafeSqlEntity (I "excluded") tableName = unEntityNameDB . getEntityDBName . entityDef - entCurrent = EEntity $ I (tableName proxy) + entCurrent = unsafeSqlEntity (I (tableName proxy)) uniqueDef = toUniqueDef unique constraint = TLB.fromText . unConstraintNameDB . uniqueDBName $ uniqueDef renderedUpdates :: (BackendCompatible SqlBackend backend) => backend -> (TLB.Builder, [PersistValue]) @@ -357,13 +357,11 @@ filterWhere -> SqlExpr (Value Bool) -- ^ Filter clause -> SqlExpr (Value a) -filterWhere aggExpr clauseExpr = ERaw Never $ \info -> +filterWhere aggExpr clauseExpr = ERaw noMeta $ \_ info -> let (aggBuilder, aggValues) = case aggExpr of - ERaw _ aggF -> aggF info - ECompositeKey _ -> throw $ CompositeKeyErr FilterWhereAggError + ERaw _ aggF -> aggF Never info (clauseBuilder, clauseValues) = case clauseExpr of - ERaw _ clauseF -> clauseF info - ECompositeKey _ -> throw $ CompositeKeyErr FilterWhereClauseError + ERaw _ clauseF -> clauseF Never info in ( aggBuilder <> " FILTER (WHERE " <> clauseBuilder <> ")" , aggValues <> clauseValues ) diff --git a/stack-8.10.yaml b/stack-8.10.yaml index 82d1ac7..0728340 100644 --- a/stack-8.10.yaml +++ b/stack-8.10.yaml @@ -6,7 +6,6 @@ packages: extra-deps: - lift-type-0.1.0.1 -- attoparsec-0.14.1 - persistent-2.13.0.0 - persistent-sqlite-2.13.0.0 - persistent-mysql-2.13.0.0 diff --git a/test/Common/Test.hs b/test/Common/Test.hs index 47491ef..598a7ca 100644 --- a/test/Common/Test.hs +++ b/test/Common/Test.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP #-} -{-# LANGUAGE DataKinds #-} {-# LANGUAGE ConstraintKinds #-} +{-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE EmptyDataDecls #-} @@ -387,7 +387,7 @@ testSubSelect run = do v `shouldBe` [Value 1] describe "subSelectList" $ do - it "is safe on empty databases as well as good databases" $ do + it "is safe on empty databases as well as good databases" $ run $ do let query = from $ \n -> do where_ $ n ^. NumbersInt `in_` do @@ -396,16 +396,15 @@ testSubSelect run = do where_ $ n' ^. NumbersInt >=. val 3 pure (n' ^. NumbersInt) pure n + empty <- select query - empty <- run $ do - select query - - full <- run $ do + full <- do setup select query - empty `shouldBe` [] - full `shouldSatisfy` (not . null) + liftIO $ do + empty `shouldBe` [] + full `shouldSatisfy` (not . null) describe "subSelectMaybe" $ do it "is equivalent to joinV . subSelect" $ do @@ -890,12 +889,14 @@ testSelectSubQuery run = describe "select subquery" $ do l1Deeds <- mapM (\k -> insert' $ Deed k (entityKey l1e)) (map show [1..3 :: Int]) let l1WithDeeds = do d <- l1Deeds pure (l1e, Just d) - ret <- select $ Experimental.from $ do - (lords :& deeds) <- - Experimental.from $ Table @Lord - `LeftOuterJoin` Table @Deed - `Experimental.on` (\(l :& d) -> just (l ^. LordId) ==. d ?. DeedOwnerId) - pure (lords, deeds) + let q = Experimental.from $ do + (lords :& deeds) <- + Experimental.from $ Table @Lord + `LeftOuterJoin` Table @Deed + `Experimental.on` (\(l :& d) -> just (l ^. LordId) ==. d ?. DeedOwnerId) + pure (lords, deeds) + + ret <- select q liftIO $ ret `shouldMatchList` ((l3e, Nothing) : l1WithDeeds) it "lets you order by alias" $ run $ do @@ -1080,17 +1081,6 @@ testSelectWhere run = describe "select where_" $ do ( val $ PointKey 1 2 , val $ PointKey 5 6 ) liftIO $ ret `shouldBe` [()] - it "works when using ECompositeKey constructor" $ run $ do - insert_ $ Point 1 2 "" - ret <- - select $ - from $ \p -> do - where_ $ - p ^. PointId - `between` - ( EI.ECompositeKey $ const ["3", "4"] - , EI.ECompositeKey $ const ["5", "6"] ) - liftIO $ ret `shouldBe` [] it "works with avg_" $ run $ do _ <- insert' p1 @@ -1868,9 +1858,10 @@ testRenderSql run = do (c, expr) <- run $ do conn <- ask let Right c = P.mkEscapeChar conn + let user = EI.unsafeSqlEntity (EI.I "user") + blogPost = EI.unsafeSqlEntity (EI.I "blog_post") pure $ (,) c $ EI.renderExpr conn $ - EI.EEntity (EI.I "user") ^. PersonId - ==. EI.EEntity (EI.I "blog_post") ^. BlogPostAuthorId + user ^. PersonId ==. blogPost ^. BlogPostAuthorId expr `shouldBe` Text.intercalate (Text.singleton c) ["", "user", ".", "id", ""] @@ -1882,23 +1873,6 @@ testRenderSql run = do expr <- run $ ask >>= \c -> pure $ EI.renderExpr c (val (PersonKey 0) ==. val (PersonKey 1)) expr `shouldBe` "? = ?" - describe "EEntity Ident behavior" $ do - let render :: SqlExpr (Entity val) -> Text.Text - render (EI.EEntity (EI.I ident)) = ident - render _ = error "guess we gotta handle this in the test suite now" - it "renders sensibly" $ run $ do - _ <- insert $ Foo 2 - _ <- insert $ Foo 3 - _ <- insert $ Person "hello" Nothing Nothing 3 - results <- select $ - from $ \(a `LeftOuterJoin` b) -> do - on $ a ^. FooName ==. b ^. PersonFavNum - pure (val (render a), val (render b)) - liftIO $ - head results - `shouldBe` - (Value "Foo", Value "Person") - describe "ExprParser" $ do let parse parser = AP.parseOnly (parser '#') describe "parseEscapedChars" $ do diff --git a/test/MySQL/Test.hs b/test/MySQL/Test.hs index 61bc7a0..20e5e1a 100644 --- a/test/MySQL/Test.hs +++ b/test/MySQL/Test.hs @@ -24,6 +24,7 @@ import Database.Persist.MySQL , defaultConnectInfo , withMySQLConn ) + import System.Environment import Test.Hspec @@ -190,7 +191,7 @@ testMysqlUnionWithLimits = do pure $ foo ^. FooName - ret <- select $ Experimental.from $ SelectQuery q1 `Union` SelectQuery q2 + ret <- select $ Experimental.from $ q1 `union_` q2 liftIO $ ret `shouldMatchList` [Value 1, Value 2, Value 4, Value 5] diff --git a/test/SQLite/Test.hs b/test/SQLite/Test.hs index 5eb198a..c124986 100644 --- a/test/SQLite/Test.hs +++ b/test/SQLite/Test.hs @@ -1,21 +1,20 @@ -{-# LANGUAGE ScopedTypeVariables - , FlexibleContexts - , RankNTypes - , TypeFamilies - , OverloadedStrings -#-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeFamilies #-} module Main (main) where import Control.Monad (void) import Control.Monad.IO.Class (MonadIO(liftIO)) -import Control.Monad.Logger (runStderrLoggingT, runNoLoggingT) +import Control.Monad.Logger (runNoLoggingT, runStderrLoggingT) import Control.Monad.Trans.Reader (ReaderT) -import Database.Persist.Sqlite (withSqliteConn) -import Database.Sqlite (SqliteException) +import qualified Control.Monad.Trans.Resource as R import Database.Esqueleto hiding (random_) import Database.Esqueleto.SQLite (random_) -import qualified Control.Monad.Trans.Resource as R +import Database.Persist.Sqlite (withSqliteConn) +import Database.Sqlite (SqliteException) import Test.Hspec import Common.Test @@ -169,7 +168,7 @@ main = do describe "Test SQLite locking" $ do testLocking withConn - fdescribe "SQLite specific tests" $ do + describe "SQLite specific tests" $ do testAscRandom random_ run testRandomMath run testSqliteRandom