Merge branch 'master' into format-config
This commit is contained in:
commit
51c546aed3
@ -1,3 +1,9 @@
|
||||
3.4.0.1
|
||||
=======
|
||||
- @arthurxavierx
|
||||
- [#221](https://github.com/bitemyapp/esqueleto/pull/221)
|
||||
- Deprecate `ToAliasT` and `ToAliasReferenceT`
|
||||
|
||||
3.4.0.0
|
||||
=======
|
||||
- @belevy, @charukiewicz
|
||||
|
||||
@ -1,7 +1,7 @@
|
||||
cabal-version: 1.12
|
||||
|
||||
name: esqueleto
|
||||
version: 3.4.0.0
|
||||
version: 3.4.0.1
|
||||
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.
|
||||
.
|
||||
|
||||
@ -56,9 +56,7 @@ module Database.Esqueleto.Experimental
|
||||
, ToMaybe(..)
|
||||
, ToMaybeT
|
||||
, ToAlias(..)
|
||||
, ToAliasT
|
||||
, ToAliasReference(..)
|
||||
, ToAliasReferenceT
|
||||
-- * The Normal Stuff
|
||||
|
||||
, where_
|
||||
@ -649,89 +647,75 @@ pattern SelectQuery q = SelectQueryP Never q
|
||||
-- select $ from $ Table \@People
|
||||
-- @
|
||||
data From a where
|
||||
Table
|
||||
:: PersistEntity ent
|
||||
=> From (SqlExpr (Entity ent))
|
||||
SubQuery
|
||||
:: ( SqlSelect a' r
|
||||
, SqlSelect a'' r'
|
||||
, ToAlias a
|
||||
, a' ~ ToAliasT a
|
||||
, ToAliasReference a'
|
||||
, ToAliasReferenceT a' ~ a''
|
||||
)
|
||||
=> SqlQuery a
|
||||
-> From a''
|
||||
FromCte
|
||||
:: Ident
|
||||
-> a
|
||||
-> From a
|
||||
SqlSetOperation
|
||||
:: ( SqlSelect a' r
|
||||
, ToAlias a
|
||||
, a' ~ ToAliasT a
|
||||
, ToAliasReference a'
|
||||
, ToAliasReferenceT a' ~ a''
|
||||
)
|
||||
=> SqlSetOperation a
|
||||
-> From a''
|
||||
InnerJoinFrom
|
||||
:: From a
|
||||
-> (From b, (a :& b) -> SqlExpr (Value Bool))
|
||||
-> From (a :& b)
|
||||
InnerJoinFromLateral
|
||||
:: ( SqlSelect b' r
|
||||
, SqlSelect b'' r'
|
||||
, ToAlias b
|
||||
, b' ~ ToAliasT b
|
||||
, ToAliasReference b'
|
||||
, ToAliasReferenceT b' ~ 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
|
||||
, SqlSelect b'' r'
|
||||
, ToAlias b
|
||||
, b' ~ ToAliasT b
|
||||
, ToAliasReference b'
|
||||
, ToAliasReferenceT b' ~ 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
|
||||
, SqlSelect b'' r'
|
||||
, ToAlias b
|
||||
, b' ~ ToAliasT b
|
||||
, ToAliasReference b'
|
||||
, ToAliasReferenceT b' ~ 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)
|
||||
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
|
||||
@ -763,23 +747,24 @@ type JoinErrorMsg jk = 'Text "Missing on statement for " ':<>: 'Text jk
|
||||
|
||||
type family ToFromT a where
|
||||
ToFromT (From a) = a
|
||||
ToFromT (SqlQuery a) = ToAliasReferenceT (ToAliasT a)
|
||||
ToFromT (Union a b) = ToAliasReferenceT (ToAliasT (SetOperationT a))
|
||||
ToFromT (UnionAll a b) = ToAliasReferenceT (ToAliasT (SetOperationT a))
|
||||
ToFromT (Except a b) = ToAliasReferenceT (ToAliasT (SetOperationT a))
|
||||
ToFromT (Intersect a b) = ToAliasReferenceT (ToAliasT (SetOperationT a))
|
||||
ToFromT (SqlSetOperation a) = ToAliasReferenceT (ToAliasT a)
|
||||
ToFromT (SqlQuery a) = a
|
||||
ToFromT (Union a b) = SetOperationT a
|
||||
ToFromT (UnionAll a b) = SetOperationT a
|
||||
ToFromT (Except a b) = SetOperationT a
|
||||
ToFromT (Intersect a b) = SetOperationT a
|
||||
ToFromT (SqlSetOperation a) = a
|
||||
ToFromT (InnerJoin a (b, c -> SqlExpr (Value Bool))) = c
|
||||
ToFromT (LeftOuterJoin a (b, c -> SqlExpr (Value Bool))) = c
|
||||
ToFromT (RightOuterJoin a (b, c -> SqlExpr (Value Bool))) = c
|
||||
ToFromT (FullOuterJoin a (b, c -> SqlExpr (Value Bool))) = c
|
||||
ToFromT (CrossJoin a (c -> SqlQuery b)) = ToFromT a :& ToAliasReferenceT (ToAliasT b)
|
||||
ToFromT (CrossJoin a (c -> SqlQuery b)) = ToFromT a :& b
|
||||
ToFromT (CrossJoin a b) = ToFromT a :& ToFromT b
|
||||
ToFromT (InnerJoin a b) = TypeError (JoinErrorMsg "InnerJoin")
|
||||
ToFromT (LeftOuterJoin a b) = TypeError (JoinErrorMsg "LeftOuterJoin")
|
||||
ToFromT (RightOuterJoin a b) = TypeError (JoinErrorMsg "RightOuterJoin")
|
||||
ToFromT (FullOuterJoin a b) = TypeError (JoinErrorMsg "FullOuterJoin")
|
||||
|
||||
|
||||
data Lateral
|
||||
data NotLateral
|
||||
|
||||
@ -805,104 +790,60 @@ instance {-# OVERLAPPABLE #-} ToFrom (LeftOuterJoin a b) where
|
||||
instance {-# OVERLAPPABLE #-} ToFrom (RightOuterJoin a b) where
|
||||
toFrom = undefined
|
||||
instance {-# OVERLAPPABLE #-} ToFrom (FullOuterJoin a b) where
|
||||
toFrom = undefined
|
||||
|
||||
instance
|
||||
( ToAlias a
|
||||
, a' ~ ToAliasT a
|
||||
, ToAliasReference a'
|
||||
, a'' ~ ToAliasReferenceT a'
|
||||
, SqlSelect a' r'
|
||||
, SqlSelect a'' r'
|
||||
)
|
||||
=>
|
||||
ToFrom (SqlQuery a)
|
||||
where
|
||||
toFrom = SubQuery
|
||||
toFrom = undefined
|
||||
|
||||
instance
|
||||
( SqlSelect c' r
|
||||
, SqlSelect c'' r'
|
||||
, ToAlias c
|
||||
, c' ~ ToAliasT c
|
||||
, ToAliasReference c'
|
||||
, ToAliasReferenceT c' ~ c''
|
||||
, ToSetOperation a c
|
||||
, ToSetOperation b c
|
||||
, c ~ SetOperationT a
|
||||
)
|
||||
=>
|
||||
ToFrom (Union a b)
|
||||
where
|
||||
toFrom u = SqlSetOperation $ toSetOperation u
|
||||
instance ( ToAlias a
|
||||
, ToAliasReference a
|
||||
, SqlSelect a r
|
||||
) => ToFrom (SqlQuery a) where
|
||||
toFrom = SubQuery
|
||||
|
||||
instance
|
||||
( SqlSelect c' r
|
||||
, SqlSelect c'' r'
|
||||
, ToAlias c
|
||||
, c' ~ ToAliasT c
|
||||
, ToAliasReference c'
|
||||
, ToAliasReferenceT c' ~ c''
|
||||
, ToSetOperation a c
|
||||
, ToSetOperation b c
|
||||
, c ~ SetOperationT a
|
||||
)
|
||||
=>
|
||||
ToFrom (UnionAll a b)
|
||||
where
|
||||
toFrom u = SqlSetOperation $ toSetOperation u
|
||||
instance ( SqlSelect c r
|
||||
, ToAlias c
|
||||
, ToAliasReference c
|
||||
, ToSetOperation a c
|
||||
, ToSetOperation b c
|
||||
, c ~ SetOperationT a
|
||||
) => ToFrom (Union a b) where
|
||||
toFrom u = SqlSetOperation $ toSetOperation u
|
||||
|
||||
instance
|
||||
( SqlSelect a' r
|
||||
, SqlSelect a'' r'
|
||||
, ToAlias a
|
||||
, a' ~ ToAliasT a
|
||||
, ToAliasReference a'
|
||||
, ToAliasReferenceT a' ~ a''
|
||||
)
|
||||
=>
|
||||
ToFrom (SqlSetOperation a)
|
||||
where
|
||||
-- If someone uses just a plain SelectQuery it should behave like a normal subquery
|
||||
toFrom (SelectQueryP _ q) = SubQuery q
|
||||
-- Otherwise use the SqlSetOperation
|
||||
toFrom q = SqlSetOperation q
|
||||
instance ( SqlSelect c r
|
||||
, ToAlias c
|
||||
, ToAliasReference c
|
||||
, ToSetOperation a c
|
||||
, ToSetOperation b c
|
||||
, c ~ SetOperationT a
|
||||
) => ToFrom (UnionAll a b) where
|
||||
toFrom u = SqlSetOperation $ toSetOperation u
|
||||
|
||||
instance (SqlSelect a r, ToAlias a, ToAliasReference a) => ToFrom (SqlSetOperation a) where
|
||||
-- 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
|
||||
toInnerJoin :: Proxy lateral -> lhs -> rhs -> (res -> SqlExpr (Value Bool)) -> From res
|
||||
|
||||
instance
|
||||
( SqlSelect bAlias r
|
||||
, SqlSelect bAliasRef r'
|
||||
, ToAlias b
|
||||
, bAlias ~ ToAliasT b
|
||||
, ToAliasReference bAlias
|
||||
, bAliasRef ~ ToAliasReferenceT bAlias
|
||||
, ToFrom a
|
||||
, ToFromT a ~ a'
|
||||
)
|
||||
=>
|
||||
ToInnerJoin Lateral a (a' -> SqlQuery b) (a' :& bAliasRef)
|
||||
where
|
||||
toInnerJoin _ lhs q on' = InnerJoinFromLateral (toFrom lhs) (q, on')
|
||||
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 (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
|
||||
( ToFrom a
|
||||
, ToFromT a ~ a'
|
||||
, ToInnerJoin (IsLateral b) a b b'
|
||||
)
|
||||
=>
|
||||
ToFrom (InnerJoin a (b, b' -> SqlExpr (Value Bool)))
|
||||
where
|
||||
toFrom (InnerJoin lhs (rhs, on')) =
|
||||
let
|
||||
instance ( ToFrom a
|
||||
, ToFromT a ~ a'
|
||||
, ToInnerJoin (IsLateral b) a b b'
|
||||
) => ToFrom (InnerJoin a (b, b' -> SqlExpr (Value Bool))) where
|
||||
toFrom (InnerJoin lhs (rhs, on')) =
|
||||
let
|
||||
toProxy :: b -> Proxy (IsLateral b)
|
||||
toProxy _ = Proxy
|
||||
in toInnerJoin (toProxy rhs) lhs rhs on'
|
||||
@ -918,61 +859,43 @@ instance
|
||||
toFrom (CrossJoin lhs rhs) = CrossJoinFrom (toFrom lhs) (toFrom rhs)
|
||||
|
||||
instance {-# OVERLAPPING #-}
|
||||
( ToFrom a
|
||||
, ToFromT a ~ a'
|
||||
, SqlSelect bAlias r
|
||||
, SqlSelect bAliasRef r'
|
||||
, ToAlias b
|
||||
, bAlias ~ ToAliasT b
|
||||
, ToAliasReference bAlias
|
||||
, bAliasRef ~ ToAliasReferenceT bAlias
|
||||
)
|
||||
=>
|
||||
ToFrom (CrossJoin a (a' -> SqlQuery b))
|
||||
where
|
||||
toFrom (CrossJoin lhs q) = CrossJoinFromLateral (toFrom lhs) q
|
||||
|
||||
( ToFrom a
|
||||
, ToFromT a ~ a'
|
||||
, SqlSelect b r
|
||||
, ToAlias b
|
||||
, ToAliasReference b
|
||||
)
|
||||
=> ToFrom (CrossJoin a (a' -> SqlQuery b)) where
|
||||
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
|
||||
toLeftJoin :: Proxy lateral -> lhs -> rhs -> (res -> SqlExpr (Value Bool)) -> From res
|
||||
|
||||
instance
|
||||
( ToFrom a
|
||||
, ToFromT a ~ a'
|
||||
, SqlSelect bAlias r
|
||||
, SqlSelect bAliasRef r'
|
||||
, ToAlias b
|
||||
, bAlias ~ ToAliasT b
|
||||
, ToAliasReference bAlias
|
||||
, bAliasRef ~ ToAliasReferenceT bAlias
|
||||
, ToMaybe bAliasRef
|
||||
, mb ~ ToMaybeT bAliasRef
|
||||
)
|
||||
=>
|
||||
ToLeftJoin Lateral a (a' -> SqlQuery b) (a' :& mb)
|
||||
where
|
||||
toLeftJoin _ lhs q on' = LeftJoinFromLateral (toFrom lhs) (q, on')
|
||||
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 ( 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
|
||||
toFrom (LeftOuterJoin lhs (rhs, on')) =
|
||||
let toProxy :: b -> Proxy (IsLateral b)
|
||||
instance ( ToLeftJoin (IsLateral b) a b b'
|
||||
) => ToFrom (LeftOuterJoin a (b, b' -> SqlExpr (Value Bool))) where
|
||||
toFrom (LeftOuterJoin lhs (rhs, on')) =
|
||||
let
|
||||
toProxy :: b -> Proxy (IsLateral b)
|
||||
toProxy _ = Proxy
|
||||
in toLeftJoin (toProxy rhs) lhs rhs on'
|
||||
|
||||
@ -1245,18 +1168,13 @@ from parts = do
|
||||
let ret = (toMaybe leftVal) :& (toMaybe rightVal)
|
||||
pure $ (ret, FromJoin leftFrom FullOuterJoinKind rightFrom (Just (on' ret)))
|
||||
|
||||
fromSubQuery
|
||||
::
|
||||
( SqlSelect a' r
|
||||
, SqlSelect a'' r'
|
||||
fromSubQuery
|
||||
::
|
||||
( SqlSelect a r
|
||||
, ToAlias a
|
||||
, a' ~ ToAliasT a
|
||||
, ToAliasReference a'
|
||||
, ToAliasReferenceT a' ~ a''
|
||||
, ToAliasReference a
|
||||
)
|
||||
=> SubQueryType
|
||||
-> SqlQuery a
|
||||
-> SqlQuery (ToAliasReferenceT (ToAliasT a), FromClause)
|
||||
=> 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
|
||||
@ -1293,9 +1211,9 @@ fromSubQuery subqueryType subquery = do
|
||||
--
|
||||
-- /Since: 3.4.0.0/
|
||||
with :: ( ToAlias a
|
||||
, ToAliasReference (ToAliasT a)
|
||||
, SqlSelect (ToAliasT a) r
|
||||
) => SqlQuery a -> SqlQuery (From (ToAliasReferenceT (ToAliasT 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
|
||||
@ -1339,16 +1257,14 @@ with query = do
|
||||
--
|
||||
-- /Since: 3.4.0.0/
|
||||
withRecursive :: ( ToAlias a
|
||||
, ToAliasReference (ToAliasT a)
|
||||
, ToAliasReference a
|
||||
, SqlSelect a r
|
||||
, SqlSelect (ToAliasT a) r
|
||||
, ref ~ ToAliasReferenceT (ToAliasT a)
|
||||
, RecursiveCteUnion unionKind
|
||||
)
|
||||
=> SqlQuery a
|
||||
-> unionKind
|
||||
-> (From ref -> SqlQuery a)
|
||||
-> SqlQuery (From ref)
|
||||
-> (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
|
||||
@ -1365,21 +1281,12 @@ withRecursive baseCase unionKind recursiveCase = do
|
||||
Q $ W.tell mempty{sdCteClause = [clause]}
|
||||
pure refFrom
|
||||
|
||||
type family ToAliasT a where
|
||||
ToAliasT (SqlExpr (Value a)) = SqlExpr (Value a)
|
||||
ToAliasT (SqlExpr (Entity a)) = SqlExpr (Entity a)
|
||||
ToAliasT (SqlExpr (Maybe (Entity a))) = SqlExpr (Maybe (Entity a))
|
||||
ToAliasT (a, b) = (ToAliasT a, ToAliasT b)
|
||||
ToAliasT (a, b, c) = (ToAliasT a, ToAliasT b, ToAliasT c)
|
||||
ToAliasT (a, b, c, d) = (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d)
|
||||
ToAliasT (a, b, c, d, e) = (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e)
|
||||
ToAliasT (a, b, c, d, e, f) = (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e, ToAliasT f)
|
||||
ToAliasT (a, b, c, d, e, f, g) = (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e, ToAliasT f, ToAliasT g)
|
||||
ToAliasT (a, b, c, d, e, f, g, h) = (ToAliasT a, ToAliasT b, ToAliasT c, ToAliasT d, ToAliasT e, ToAliasT f, ToAliasT g, ToAliasT h)
|
||||
{-# 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 (ToAliasT a)
|
||||
toAlias :: a -> SqlQuery a
|
||||
|
||||
instance ToAlias (SqlExpr (Value a)) where
|
||||
toAlias v@(EAliasedValue _ _) = pure v
|
||||
@ -1451,22 +1358,12 @@ instance ( ToAlias a
|
||||
) => ToAlias (a,b,c,d,e,f,g,h) where
|
||||
toAlias x = to8 <$> (toAlias $ from8 x)
|
||||
|
||||
|
||||
type family ToAliasReferenceT a where
|
||||
ToAliasReferenceT (SqlExpr (Value a)) = SqlExpr (Value a)
|
||||
ToAliasReferenceT (SqlExpr (Entity a)) = SqlExpr (Entity a)
|
||||
ToAliasReferenceT (SqlExpr (Maybe (Entity a))) = SqlExpr (Maybe (Entity a))
|
||||
ToAliasReferenceT (a,b) = (ToAliasReferenceT a, ToAliasReferenceT b)
|
||||
ToAliasReferenceT (a,b,c) = (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c)
|
||||
ToAliasReferenceT (a, b, c, d) = (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c, ToAliasReferenceT d)
|
||||
ToAliasReferenceT (a, b, c, d, e) = (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c, ToAliasReferenceT d, ToAliasReferenceT e)
|
||||
ToAliasReferenceT (a, b, c, d, e, f) = (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c, ToAliasReferenceT d, ToAliasReferenceT e, ToAliasReferenceT f)
|
||||
ToAliasReferenceT (a, b, c, d, e, f, g) = (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c, ToAliasReferenceT d, ToAliasReferenceT e, ToAliasReferenceT f, ToAliasReferenceT g)
|
||||
ToAliasReferenceT (a, b, c, d, e, f, g, h) = (ToAliasReferenceT a, ToAliasReferenceT b, ToAliasReferenceT c, ToAliasReferenceT d, ToAliasReferenceT e, ToAliasReferenceT f, ToAliasReferenceT g, ToAliasReferenceT h)
|
||||
{-# 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 (ToAliasReferenceT a)
|
||||
toAliasReference :: Ident -> a -> SqlQuery a
|
||||
|
||||
instance ToAliasReference (SqlExpr (Value a)) where
|
||||
toAliasReference aliasSource (EAliasedValue aliasIdent _) = pure $ EValueReference aliasSource (\_ -> aliasIdent)
|
||||
@ -1482,6 +1379,7 @@ instance ToAliasReference (SqlExpr (Entity a)) where
|
||||
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)
|
||||
|
||||
|
||||
Loading…
Reference in New Issue
Block a user