{-# 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
class ToAlias a where
toAlias :: a -> SqlQuery a
instance ToAlias (SqlExpr (Value a)) where
toAlias :: SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a))
toAlias e :: SqlExpr (Value a)
e@(ERaw SqlExprMeta
m NeedParens -> IdentInfo -> (Builder, [PersistValue])
f)
| Just Ident
_ <- SqlExprMeta -> Maybe Ident
sqlExprMetaAlias SqlExprMeta
m = forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlExpr (Value a)
e
| Bool
otherwise = do
Ident
ident <- DBName -> SqlQuery Ident
newIdentFor (Text -> DBName
DBName Text
"v")
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a.
SqlExprMeta
-> (NeedParens -> IdentInfo -> (Builder, [PersistValue]))
-> SqlExpr a
ERaw SqlExprMeta
noMeta{sqlExprMetaAlias :: Maybe Ident
sqlExprMetaAlias = forall a. a -> Maybe a
Just Ident
ident} NeedParens -> IdentInfo -> (Builder, [PersistValue])
f
instance ToAlias (SqlExpr (Entity a)) where
toAlias :: SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a))
toAlias e :: SqlExpr (Entity a)
e@(ERaw SqlExprMeta
m NeedParens -> IdentInfo -> (Builder, [PersistValue])
f)
| Just Ident
_ <- SqlExprMeta -> Maybe Ident
sqlExprMetaAlias SqlExprMeta
m = forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlExpr (Entity a)
e
| Bool
otherwise = do
Ident
ident <- DBName -> SqlQuery Ident
newIdentFor (Text -> DBName
DBName Text
"v")
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a.
SqlExprMeta
-> (NeedParens -> IdentInfo -> (Builder, [PersistValue]))
-> SqlExpr a
ERaw SqlExprMeta
m{sqlExprMetaIsReference :: Bool
sqlExprMetaIsReference = Bool
False, sqlExprMetaAlias :: Maybe Ident
sqlExprMetaAlias = forall a. a -> Maybe a
Just Ident
ident} NeedParens -> IdentInfo -> (Builder, [PersistValue])
f
instance ToAlias (SqlExpr (Maybe (Entity a))) where
toAlias :: SqlExpr (Maybe (Entity a)) -> SqlQuery (SqlExpr (Maybe (Entity a)))
toAlias e :: SqlExpr (Maybe (Entity a))
e@(ERaw SqlExprMeta
m NeedParens -> IdentInfo -> (Builder, [PersistValue])
f)
| Just Ident
_ <- SqlExprMeta -> Maybe Ident
sqlExprMetaAlias SqlExprMeta
m = forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlExpr (Maybe (Entity a))
e
| Bool
otherwise = do
Ident
ident <- DBName -> SqlQuery Ident
newIdentFor (Text -> DBName
DBName Text
"v")
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a.
SqlExprMeta
-> (NeedParens -> IdentInfo -> (Builder, [PersistValue]))
-> SqlExpr a
ERaw SqlExprMeta
m{sqlExprMetaIsReference :: Bool
sqlExprMetaIsReference = Bool
False, sqlExprMetaAlias :: Maybe Ident
sqlExprMetaAlias = forall a. a -> Maybe a
Just Ident
ident} NeedParens -> IdentInfo -> (Builder, [PersistValue])
f
instance (ToAlias a, ToAlias b) => ToAlias (a,b) where
toAlias :: (a, b) -> SqlQuery (a, b)
toAlias (a
a,b
b) = (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. ToAlias a => a -> SqlQuery a
toAlias a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. ToAlias a => a -> SqlQuery a
toAlias b
b
instance ( ToAlias a
, ToAlias b
, ToAlias c
) => ToAlias (a,b,c) where
toAlias :: (a, b, c) -> SqlQuery (a, b, c)
toAlias (a, b, c)
x = forall a b c. ((a, b), c) -> (a, b, c)
to3 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. ToAlias a => a -> SqlQuery a
toAlias forall a b. (a -> b) -> a -> b
$ forall a b c. (a, b, c) -> ((a, b), c)
from3 (a, b, c)
x)
instance ( ToAlias a
, ToAlias b
, ToAlias c
, ToAlias d
) => ToAlias (a,b,c,d) where
toAlias :: (a, b, c, d) -> SqlQuery (a, b, c, d)
toAlias (a, b, c, d)
x = forall a b c d. ((a, b), (c, d)) -> (a, b, c, d)
to4 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. ToAlias a => a -> SqlQuery a
toAlias forall a b. (a -> b) -> a -> b
$ forall a b c d. (a, b, c, d) -> ((a, b), (c, d))
from4 (a, b, c, d)
x)
instance ( ToAlias a
, ToAlias b
, ToAlias c
, ToAlias d
, ToAlias e
) => ToAlias (a,b,c,d,e) where
toAlias :: (a, b, c, d, e) -> SqlQuery (a, b, c, d, e)
toAlias (a, b, c, d, e)
x = forall a b c d e. ((a, b), (c, d), e) -> (a, b, c, d, e)
to5 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. ToAlias a => a -> SqlQuery a
toAlias forall a b. (a -> b) -> a -> b
$ forall a b c d e. (a, b, c, d, e) -> ((a, b), (c, d), e)
from5 (a, b, c, d, e)
x)
instance ( ToAlias a
, ToAlias b
, ToAlias c
, ToAlias d
, ToAlias e
, ToAlias f
) => ToAlias (a,b,c,d,e,f) where
toAlias :: (a, b, c, d, e, f) -> SqlQuery (a, b, c, d, e, f)
toAlias (a, b, c, d, e, f)
x = forall a b c d e f. ((a, b), (c, d), (e, f)) -> (a, b, c, d, e, f)
to6 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. ToAlias a => a -> SqlQuery a
toAlias forall a b. (a -> b) -> a -> b
$ forall a b c d e f. (a, b, c, d, e, f) -> ((a, b), (c, d), (e, f))
from6 (a, b, c, d, e, f)
x)
instance ( ToAlias a
, ToAlias b
, ToAlias c
, ToAlias d
, ToAlias e
, ToAlias f
, ToAlias g
) => ToAlias (a,b,c,d,e,f,g) where
toAlias :: (a, b, c, d, e, f, g) -> SqlQuery (a, b, c, d, e, f, g)
toAlias (a, b, c, d, e, f, g)
x = forall a b c d e f g.
((a, b), (c, d), (e, f), g) -> (a, b, c, d, e, f, g)
to7 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. ToAlias a => a -> SqlQuery a
toAlias forall a b. (a -> b) -> a -> b
$ forall a b c d e f g.
(a, b, c, d, e, f, g) -> ((a, b), (c, d), (e, f), g)
from7 (a, b, c, d, e, f, g)
x)
instance ( ToAlias a
, ToAlias b
, ToAlias c
, ToAlias d
, ToAlias e
, ToAlias f
, ToAlias g
, ToAlias h
) => ToAlias (a,b,c,d,e,f,g,h) where
toAlias :: (a, b, c, d, e, f, g, h) -> SqlQuery (a, b, c, d, e, f, g, h)
toAlias (a, b, c, d, e, f, g, h)
x = forall a b c d e f g h.
((a, b), (c, d), (e, f), (g, h)) -> (a, b, c, d, e, f, g, h)
to8 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. ToAlias a => a -> SqlQuery a
toAlias forall a b. (a -> b) -> a -> b
$ forall a b c d e f g h.
(a, b, c, d, e, f, g, h) -> ((a, b), (c, d), (e, f), (g, h))
from8 (a, b, c, d, e, f, g, h)
x)
instance ( ToAlias a
, ToAlias b
, ToAlias c
, ToAlias d
, ToAlias e
, ToAlias f
, ToAlias g
, ToAlias h
, ToAlias i
) => ToAlias (a,b,c,d,e,f,g,h,i) where
toAlias :: (a, b, c, d, e, f, g, h, i) -> SqlQuery (a, b, c, d, e, f, g, h, i)
toAlias (a, b, c, d, e, f, g, h, i)
x = forall a b c d e f g h i.
((a, b), (c, d), (e, f), (g, h), i) -> (a, b, c, d, e, f, g, h, i)
to9 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. ToAlias a => a -> SqlQuery a
toAlias forall a b. (a -> b) -> a -> b
$ forall a b c d e f g h i.
(a, b, c, d, e, f, g, h, i) -> ((a, b), (c, d), (e, f), (g, h), i)
from9 (a, b, c, d, e, f, g, h, i)
x)
instance ( ToAlias a
, ToAlias b
, ToAlias c
, ToAlias d
, ToAlias e
, ToAlias f
, ToAlias g
, ToAlias h
, ToAlias i
, ToAlias j
) => ToAlias (a,b,c,d,e,f,g,h,i,j) where
toAlias :: (a, b, c, d, e, f, g, h, i, j)
-> SqlQuery (a, b, c, d, e, f, g, h, i, j)
toAlias (a, b, c, d, e, f, g, h, i, j)
x = forall a b c d e f g h i j.
((a, b), (c, d), (e, f), (g, h), (i, j))
-> (a, b, c, d, e, f, g, h, i, j)
to10 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. ToAlias a => a -> SqlQuery a
toAlias forall a b. (a -> b) -> a -> b
$ forall a b c d e f g h i j.
(a, b, c, d, e, f, g, h, i, j)
-> ((a, b), (c, d), (e, f), (g, h), (i, j))
from10 (a, b, c, d, e, f, g, h, i, j)
x)
instance ( ToAlias a
, ToAlias b
, ToAlias c
, ToAlias d
, ToAlias e
, ToAlias f
, ToAlias g
, ToAlias h
, ToAlias i
, ToAlias j
, ToAlias k
) => ToAlias (a,b,c,d,e,f,g,h,i,j,k) where
toAlias :: (a, b, c, d, e, f, g, h, i, j, k)
-> SqlQuery (a, b, c, d, e, f, g, h, i, j, k)
toAlias (a, b, c, d, e, f, g, h, i, j, k)
x = forall a b c d e f g h i j k.
((a, b), (c, d), (e, f), (g, h), (i, j), k)
-> (a, b, c, d, e, f, g, h, i, j, k)
to11 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. ToAlias a => a -> SqlQuery a
toAlias forall a b. (a -> b) -> a -> b
$ forall a b c d e f g h i j k.
(a, b, c, d, e, f, g, h, i, j, k)
-> ((a, b), (c, d), (e, f), (g, h), (i, j), k)
from11 (a, b, c, d, e, f, g, h, i, j, k)
x)
instance ( ToAlias a
, ToAlias b
, ToAlias c
, ToAlias d
, ToAlias e
, ToAlias f
, ToAlias g
, ToAlias h
, ToAlias i
, ToAlias j
, ToAlias k
, ToAlias l
) => ToAlias (a,b,c,d,e,f,g,h,i,j,k,l) where
toAlias :: (a, b, c, d, e, f, g, h, i, j, k, l)
-> SqlQuery (a, b, c, d, e, f, g, h, i, j, k, l)
toAlias (a, b, c, d, e, f, g, h, i, j, k, l)
x = forall a b c d e f g h i j k l.
((a, b), (c, d), (e, f), (g, h), (i, j), (k, l))
-> (a, b, c, d, e, f, g, h, i, j, k, l)
to12 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. ToAlias a => a -> SqlQuery a
toAlias forall a b. (a -> b) -> a -> b
$ forall a b c d e f g h i j k l.
(a, b, c, d, e, f, g, h, i, j, k, l)
-> ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l))
from12 (a, b, c, d, e, f, g, h, i, j, k, l)
x)
instance ( ToAlias a
, ToAlias b
, ToAlias c
, ToAlias d
, ToAlias e
, ToAlias f
, ToAlias g
, ToAlias h
, ToAlias i
, ToAlias j
, ToAlias k
, ToAlias l
, ToAlias m
) => ToAlias (a,b,c,d,e,f,g,h,i,j,k,l,m) where
toAlias :: (a, b, c, d, e, f, g, h, i, j, k, l, m)
-> SqlQuery (a, b, c, d, e, f, g, h, i, j, k, l, m)
toAlias (a, b, c, d, e, f, g, h, i, j, k, l, m)
x = forall a b c d e f g h i j k l m.
((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), m)
-> (a, b, c, d, e, f, g, h, i, j, k, l, m)
to13 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. ToAlias a => a -> SqlQuery a
toAlias forall a b. (a -> b) -> a -> b
$ forall a b c d e f g h i j k l m.
(a, b, c, d, e, f, g, h, i, j, k, l, m)
-> ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), m)
from13 (a, b, c, d, e, f, g, h, i, j, k, l, m)
x)
instance ( ToAlias a
, ToAlias b
, ToAlias c
, ToAlias d
, ToAlias e
, ToAlias f
, ToAlias g
, ToAlias h
, ToAlias i
, ToAlias j
, ToAlias k
, ToAlias l
, ToAlias m
, ToAlias n
) => ToAlias (a,b,c,d,e,f,g,h,i,j,k,l,m,n) where
toAlias :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
-> SqlQuery (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
toAlias (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
x = forall a b c d e f g h i j k l m n.
((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n))
-> (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
to14 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. ToAlias a => a -> SqlQuery a
toAlias forall a b. (a -> b) -> a -> b
$ forall a b c d e f g h i j k l m n.
(a, b, c, d, e, f, g, h, i, j, k, l, m, n)
-> ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n))
from14 (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
x)
instance ( ToAlias a
, ToAlias b
, ToAlias c
, ToAlias d
, ToAlias e
, ToAlias f
, ToAlias g
, ToAlias h
, ToAlias i
, ToAlias j
, ToAlias k
, ToAlias l
, ToAlias m
, ToAlias n
, ToAlias o
) => ToAlias (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o) where
toAlias :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
-> SqlQuery (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
toAlias (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
x = forall a b c d e f g h i j k l m n o.
((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n), o)
-> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
to15 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. ToAlias a => a -> SqlQuery a
toAlias forall a b. (a -> b) -> a -> b
$ forall a b c d e f g h i j k l m n o.
(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
-> ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n), o)
from15 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
x)
instance ( ToAlias a
, ToAlias b
, ToAlias c
, ToAlias d
, ToAlias e
, ToAlias f
, ToAlias g
, ToAlias h
, ToAlias i
, ToAlias j
, ToAlias k
, ToAlias l
, ToAlias m
, ToAlias n
, ToAlias o
, ToAlias p
) => ToAlias (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p) where
toAlias :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)
-> SqlQuery (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)
toAlias (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)
x = forall a b c d e f g h i j k l m n o p.
((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n), (o, p))
-> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)
to16 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. ToAlias a => a -> SqlQuery a
toAlias forall a b. (a -> b) -> a -> b
$ forall a b c d e f g h i j k l m n o p.
(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)
-> ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n), (o, p))
from16 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)
x)