{-# 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 :: Ident -> SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a))
toAliasReference Ident
aliasSource (ERaw SqlExprMeta
m NeedParens -> IdentInfo -> (Builder, [PersistValue])
_)
      | Just Ident
alias <- SqlExprMeta -> Maybe Ident
sqlExprMetaAlias SqlExprMeta
m = 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
True} forall a b. (a -> b) -> a -> b
$ \NeedParens
_ IdentInfo
info ->
          (IdentInfo -> Ident -> Builder
useIdent IdentInfo
info Ident
aliasSource forall a. Semigroup a => a -> a -> a
<> Builder
"." forall a. Semigroup a => a -> a -> a
<> IdentInfo -> Ident -> Builder
useIdent IdentInfo
info Ident
alias, [])
    toAliasReference Ident
_ SqlExpr (Value a)
e = forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlExpr (Value a)
e

instance ToAliasReference (SqlExpr (Entity a)) where
    toAliasReference :: Ident -> SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a))
toAliasReference Ident
aliasSource (ERaw SqlExprMeta
m NeedParens -> IdentInfo -> (Builder, [PersistValue])
_)
      | Just Ident
_ <- SqlExprMeta -> Maybe Ident
sqlExprMetaAlias SqlExprMeta
m =
          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
True} forall a b. (a -> b) -> a -> b
$ \NeedParens
_ IdentInfo
info ->
            (IdentInfo -> Ident -> Builder
useIdent IdentInfo
info Ident
aliasSource, [])
    toAliasReference Ident
_ SqlExpr (Entity a)
e = forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlExpr (Entity a)
e

instance ToAliasReference (SqlExpr (Maybe (Entity a))) where
    toAliasReference :: Ident
-> SqlExpr (Maybe (Entity a))
-> SqlQuery (SqlExpr (Maybe (Entity a)))
toAliasReference Ident
aliasSource SqlExpr (Maybe (Entity a))
e =
        coerce :: forall a b. Coercible a b => a -> b
coerce forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. ToAliasReference a => Ident -> a -> SqlQuery a
toAliasReference Ident
aliasSource (coerce :: forall a b. Coercible a b => a -> b
coerce SqlExpr (Maybe (Entity a))
e :: SqlExpr (Entity a))


instance (ToAliasReference a, ToAliasReference b) => ToAliasReference (a, b) where
    toAliasReference :: Ident -> (a, b) -> SqlQuery (a, b)
toAliasReference Ident
ident (a
a,b
b) = (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. ToAliasReference a => Ident -> a -> SqlQuery a
toAliasReference Ident
ident a
a) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a. ToAliasReference a => Ident -> a -> SqlQuery a
toAliasReference Ident
ident b
b)

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

instance ( ToAliasReference a
         , ToAliasReference b
         , ToAliasReference c
         , ToAliasReference d
         ) => ToAliasReference (a,b,c,d) where
    toAliasReference :: Ident -> (a, b, c, d) -> SqlQuery (a, b, c, d)
toAliasReference Ident
ident (a, b, c, d)
x = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b c d. ((a, b), (c, d)) -> (a, b, c, d)
to4 forall a b. (a -> b) -> a -> b
$ forall a. ToAliasReference a => Ident -> a -> SqlQuery a
toAliasReference Ident
ident 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 ( ToAliasReference a
         , ToAliasReference b
         , ToAliasReference c
         , ToAliasReference d
         , ToAliasReference e
         ) => ToAliasReference (a,b,c,d,e) where
    toAliasReference :: Ident -> (a, b, c, d, e) -> SqlQuery (a, b, c, d, e)
toAliasReference Ident
ident (a, b, c, d, e)
x = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b c d e. ((a, b), (c, d), e) -> (a, b, c, d, e)
to5 forall a b. (a -> b) -> a -> b
$ forall a. ToAliasReference a => Ident -> a -> SqlQuery a
toAliasReference Ident
ident 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 ( ToAliasReference a
         , ToAliasReference b
         , ToAliasReference c
         , ToAliasReference d
         , ToAliasReference e
         , ToAliasReference f
         ) => ToAliasReference (a,b,c,d,e,f) where
    toAliasReference :: Ident -> (a, b, c, d, e, f) -> SqlQuery (a, b, c, d, e, f)
toAliasReference Ident
ident (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. ToAliasReference a => Ident -> a -> SqlQuery a
toAliasReference Ident
ident 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 ( ToAliasReference a
         , ToAliasReference b
         , ToAliasReference c
         , ToAliasReference d
         , ToAliasReference e
         , ToAliasReference f
         , ToAliasReference g
         ) => ToAliasReference (a,b,c,d,e,f,g) where
    toAliasReference :: Ident -> (a, b, c, d, e, f, g) -> SqlQuery (a, b, c, d, e, f, g)
toAliasReference Ident
ident (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. ToAliasReference a => Ident -> a -> SqlQuery a
toAliasReference Ident
ident 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 ( ToAliasReference a
         , ToAliasReference b
         , ToAliasReference c
         , ToAliasReference d
         , ToAliasReference e
         , ToAliasReference f
         , ToAliasReference g
         , ToAliasReference h
         ) => ToAliasReference (a,b,c,d,e,f,g,h) where
    toAliasReference :: Ident
-> (a, b, c, d, e, f, g, h) -> SqlQuery (a, b, c, d, e, f, g, h)
toAliasReference Ident
ident (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. ToAliasReference a => Ident -> a -> SqlQuery a
toAliasReference Ident
ident 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)