fix
This commit is contained in:
parent
31f7b7f6c3
commit
17b0da892f
@ -1189,20 +1189,20 @@ from parts = do
|
||||
(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
|
||||
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)
|
||||
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
|
||||
|
||||
@ -26,7 +26,7 @@ module Database.Esqueleto.Internal.Internal where
|
||||
import Control.Applicative ((<|>))
|
||||
import Control.Arrow (first, (***))
|
||||
import Control.Exception (Exception, throw, throwIO)
|
||||
import Control.Monad (MonadPlus(..), ap, guard, void)
|
||||
import Control.Monad (MonadPlus(..), guard, void)
|
||||
import Control.Monad.IO.Class (MonadIO(..))
|
||||
import Control.Monad.Trans.Class (lift)
|
||||
import Control.Monad.Trans.Resource (MonadResource, release)
|
||||
@ -2889,7 +2889,7 @@ makeFrom info mode fs = ret
|
||||
|
||||
base ident@(I identText) def =
|
||||
let db@(DBName dbText) = entityDB def
|
||||
in ( fromDBNameinfo db <>
|
||||
in ( fromDBName info db <>
|
||||
if dbText == identText
|
||||
then mempty
|
||||
else " AS " <> useIdent info ident
|
||||
@ -3073,7 +3073,7 @@ instance SqlSelect () () where
|
||||
unescapedColumnNames :: EntityDef -> [DBName]
|
||||
unescapedColumnNames ent =
|
||||
(if hasCompositeKey ent then id else ( fieldDB (entityId ent) :))
|
||||
<> map fieldDB (entityFields ent)
|
||||
$ map fieldDB (entityFields ent)
|
||||
|
||||
-- | You may return an 'Entity' from a 'select' query.
|
||||
instance PersistEntity a => SqlSelect (SqlExpr (Entity a)) (Entity a) where
|
||||
|
||||
Loading…
Reference in New Issue
Block a user