{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE UndecidableInstances #-}
module Hasura.RQL.IR.Select.OrderBy
( AnnotatedAggregateOrderBy (..),
AggregateOrderByColumn (..),
AnnotatedOrderByElement (..),
AnnotatedOrderByItem,
AnnotatedOrderByItemG,
ComputedFieldOrderBy (..),
ComputedFieldOrderByElement (..),
)
where
import Hasura.Function.Cache
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp
import Hasura.RQL.IR.OrderBy
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.BackendType
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.ComputedField
import Hasura.RQL.Types.Relationships.Local
data AnnotatedOrderByElement (b :: BackendType) v
= AOCColumn
(ColumnInfo b)
(AnnRedactionExp b v)
| AOCObjectRelation
(RelInfo b)
(AnnBoolExp b v)
(AnnotatedOrderByElement b v)
| AOCArrayAggregation
(RelInfo b)
(AnnBoolExp b v)
(AnnotatedAggregateOrderBy b v)
| AOCComputedField (ComputedFieldOrderBy b v)
deriving stock ((forall x.
AnnotatedOrderByElement b v -> Rep (AnnotatedOrderByElement b v) x)
-> (forall x.
Rep (AnnotatedOrderByElement b v) x -> AnnotatedOrderByElement b v)
-> Generic (AnnotatedOrderByElement b v)
forall x.
Rep (AnnotatedOrderByElement b v) x -> AnnotatedOrderByElement b v
forall x.
AnnotatedOrderByElement b v -> Rep (AnnotatedOrderByElement b v) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) v x.
Rep (AnnotatedOrderByElement b v) x -> AnnotatedOrderByElement b v
forall (b :: BackendType) v x.
AnnotatedOrderByElement b v -> Rep (AnnotatedOrderByElement b v) x
$cfrom :: forall (b :: BackendType) v x.
AnnotatedOrderByElement b v -> Rep (AnnotatedOrderByElement b v) x
from :: forall x.
AnnotatedOrderByElement b v -> Rep (AnnotatedOrderByElement b v) x
$cto :: forall (b :: BackendType) v x.
Rep (AnnotatedOrderByElement b v) x -> AnnotatedOrderByElement b v
to :: forall x.
Rep (AnnotatedOrderByElement b v) x -> AnnotatedOrderByElement b v
Generic, (forall a b.
(a -> b)
-> AnnotatedOrderByElement b a -> AnnotatedOrderByElement b b)
-> (forall a b.
a -> AnnotatedOrderByElement b b -> AnnotatedOrderByElement b a)
-> Functor (AnnotatedOrderByElement b)
forall a b.
a -> AnnotatedOrderByElement b b -> AnnotatedOrderByElement b a
forall a b.
(a -> b)
-> AnnotatedOrderByElement b a -> AnnotatedOrderByElement b b
forall (b :: BackendType) a b.
Backend b =>
a -> AnnotatedOrderByElement b b -> AnnotatedOrderByElement b a
forall (b :: BackendType) a b.
Backend b =>
(a -> b)
-> AnnotatedOrderByElement b a -> AnnotatedOrderByElement b b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall (b :: BackendType) a b.
Backend b =>
(a -> b)
-> AnnotatedOrderByElement b a -> AnnotatedOrderByElement b b
fmap :: forall a b.
(a -> b)
-> AnnotatedOrderByElement b a -> AnnotatedOrderByElement b b
$c<$ :: forall (b :: BackendType) a b.
Backend b =>
a -> AnnotatedOrderByElement b b -> AnnotatedOrderByElement b a
<$ :: forall a b.
a -> AnnotatedOrderByElement b b -> AnnotatedOrderByElement b a
Functor, (forall m. Monoid m => AnnotatedOrderByElement b m -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> AnnotatedOrderByElement b a -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> AnnotatedOrderByElement b a -> m)
-> (forall a b.
(a -> b -> b) -> b -> AnnotatedOrderByElement b a -> b)
-> (forall a b.
(a -> b -> b) -> b -> AnnotatedOrderByElement b a -> b)
-> (forall b a.
(b -> a -> b) -> b -> AnnotatedOrderByElement b a -> b)
-> (forall b a.
(b -> a -> b) -> b -> AnnotatedOrderByElement b a -> b)
-> (forall a. (a -> a -> a) -> AnnotatedOrderByElement b a -> a)
-> (forall a. (a -> a -> a) -> AnnotatedOrderByElement b a -> a)
-> (forall a. AnnotatedOrderByElement b a -> [a])
-> (forall a. AnnotatedOrderByElement b a -> Bool)
-> (forall a. AnnotatedOrderByElement b a -> Int)
-> (forall a. Eq a => a -> AnnotatedOrderByElement b a -> Bool)
-> (forall a. Ord a => AnnotatedOrderByElement b a -> a)
-> (forall a. Ord a => AnnotatedOrderByElement b a -> a)
-> (forall a. Num a => AnnotatedOrderByElement b a -> a)
-> (forall a. Num a => AnnotatedOrderByElement b a -> a)
-> Foldable (AnnotatedOrderByElement b)
forall a. Eq a => a -> AnnotatedOrderByElement b a -> Bool
forall a. Num a => AnnotatedOrderByElement b a -> a
forall a. Ord a => AnnotatedOrderByElement b a -> a
forall m. Monoid m => AnnotatedOrderByElement b m -> m
forall a. AnnotatedOrderByElement b a -> Bool
forall a. AnnotatedOrderByElement b a -> Int
forall a. AnnotatedOrderByElement b a -> [a]
forall a. (a -> a -> a) -> AnnotatedOrderByElement b a -> a
forall m a.
Monoid m =>
(a -> m) -> AnnotatedOrderByElement b a -> m
forall b a. (b -> a -> b) -> b -> AnnotatedOrderByElement b a -> b
forall a b. (a -> b -> b) -> b -> AnnotatedOrderByElement b a -> b
forall (b :: BackendType) a.
(Backend b, Eq a) =>
a -> AnnotatedOrderByElement b a -> Bool
forall (b :: BackendType) a.
(Backend b, Num a) =>
AnnotatedOrderByElement b a -> a
forall (b :: BackendType) a.
(Backend b, Ord a) =>
AnnotatedOrderByElement b a -> a
forall (b :: BackendType) m.
(Backend b, Monoid m) =>
AnnotatedOrderByElement b m -> m
forall (b :: BackendType) a.
Backend b =>
AnnotatedOrderByElement b a -> Bool
forall (b :: BackendType) a.
Backend b =>
AnnotatedOrderByElement b a -> Int
forall (b :: BackendType) a.
Backend b =>
AnnotatedOrderByElement b a -> [a]
forall (b :: BackendType) a.
Backend b =>
(a -> a -> a) -> AnnotatedOrderByElement b a -> a
forall (b :: BackendType) m a.
(Backend b, Monoid m) =>
(a -> m) -> AnnotatedOrderByElement b a -> m
forall (b :: BackendType) b a.
Backend b =>
(b -> a -> b) -> b -> AnnotatedOrderByElement b a -> b
forall (b :: BackendType) a b.
Backend b =>
(a -> b -> b) -> b -> AnnotatedOrderByElement b a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall (b :: BackendType) m.
(Backend b, Monoid m) =>
AnnotatedOrderByElement b m -> m
fold :: forall m. Monoid m => AnnotatedOrderByElement b m -> m
$cfoldMap :: forall (b :: BackendType) m a.
(Backend b, Monoid m) =>
(a -> m) -> AnnotatedOrderByElement b a -> m
foldMap :: forall m a.
Monoid m =>
(a -> m) -> AnnotatedOrderByElement b a -> m
$cfoldMap' :: forall (b :: BackendType) m a.
(Backend b, Monoid m) =>
(a -> m) -> AnnotatedOrderByElement b a -> m
foldMap' :: forall m a.
Monoid m =>
(a -> m) -> AnnotatedOrderByElement b a -> m
$cfoldr :: forall (b :: BackendType) a b.
Backend b =>
(a -> b -> b) -> b -> AnnotatedOrderByElement b a -> b
foldr :: forall a b. (a -> b -> b) -> b -> AnnotatedOrderByElement b a -> b
$cfoldr' :: forall (b :: BackendType) a b.
Backend b =>
(a -> b -> b) -> b -> AnnotatedOrderByElement b a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> AnnotatedOrderByElement b a -> b
$cfoldl :: forall (b :: BackendType) b a.
Backend b =>
(b -> a -> b) -> b -> AnnotatedOrderByElement b a -> b
foldl :: forall b a. (b -> a -> b) -> b -> AnnotatedOrderByElement b a -> b
$cfoldl' :: forall (b :: BackendType) b a.
Backend b =>
(b -> a -> b) -> b -> AnnotatedOrderByElement b a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> AnnotatedOrderByElement b a -> b
$cfoldr1 :: forall (b :: BackendType) a.
Backend b =>
(a -> a -> a) -> AnnotatedOrderByElement b a -> a
foldr1 :: forall a. (a -> a -> a) -> AnnotatedOrderByElement b a -> a
$cfoldl1 :: forall (b :: BackendType) a.
Backend b =>
(a -> a -> a) -> AnnotatedOrderByElement b a -> a
foldl1 :: forall a. (a -> a -> a) -> AnnotatedOrderByElement b a -> a
$ctoList :: forall (b :: BackendType) a.
Backend b =>
AnnotatedOrderByElement b a -> [a]
toList :: forall a. AnnotatedOrderByElement b a -> [a]
$cnull :: forall (b :: BackendType) a.
Backend b =>
AnnotatedOrderByElement b a -> Bool
null :: forall a. AnnotatedOrderByElement b a -> Bool
$clength :: forall (b :: BackendType) a.
Backend b =>
AnnotatedOrderByElement b a -> Int
length :: forall a. AnnotatedOrderByElement b a -> Int
$celem :: forall (b :: BackendType) a.
(Backend b, Eq a) =>
a -> AnnotatedOrderByElement b a -> Bool
elem :: forall a. Eq a => a -> AnnotatedOrderByElement b a -> Bool
$cmaximum :: forall (b :: BackendType) a.
(Backend b, Ord a) =>
AnnotatedOrderByElement b a -> a
maximum :: forall a. Ord a => AnnotatedOrderByElement b a -> a
$cminimum :: forall (b :: BackendType) a.
(Backend b, Ord a) =>
AnnotatedOrderByElement b a -> a
minimum :: forall a. Ord a => AnnotatedOrderByElement b a -> a
$csum :: forall (b :: BackendType) a.
(Backend b, Num a) =>
AnnotatedOrderByElement b a -> a
sum :: forall a. Num a => AnnotatedOrderByElement b a -> a
$cproduct :: forall (b :: BackendType) a.
(Backend b, Num a) =>
AnnotatedOrderByElement b a -> a
product :: forall a. Num a => AnnotatedOrderByElement b a -> a
Foldable, Functor (AnnotatedOrderByElement b)
Foldable (AnnotatedOrderByElement b)
Functor (AnnotatedOrderByElement b)
-> Foldable (AnnotatedOrderByElement b)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> AnnotatedOrderByElement b a -> f (AnnotatedOrderByElement b b))
-> (forall (f :: * -> *) a.
Applicative f =>
AnnotatedOrderByElement b (f a) -> f (AnnotatedOrderByElement b a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> AnnotatedOrderByElement b a -> m (AnnotatedOrderByElement b b))
-> (forall (m :: * -> *) a.
Monad m =>
AnnotatedOrderByElement b (m a) -> m (AnnotatedOrderByElement b a))
-> Traversable (AnnotatedOrderByElement b)
forall (b :: BackendType).
Backend b =>
Functor (AnnotatedOrderByElement b)
forall (b :: BackendType).
Backend b =>
Foldable (AnnotatedOrderByElement b)
forall (b :: BackendType) (m :: * -> *) a.
(Backend b, Monad m) =>
AnnotatedOrderByElement b (m a) -> m (AnnotatedOrderByElement b a)
forall (b :: BackendType) (f :: * -> *) a.
(Backend b, Applicative f) =>
AnnotatedOrderByElement b (f a) -> f (AnnotatedOrderByElement b a)
forall (b :: BackendType) (m :: * -> *) a b.
(Backend b, Monad m) =>
(a -> m b)
-> AnnotatedOrderByElement b a -> m (AnnotatedOrderByElement b b)
forall (b :: BackendType) (f :: * -> *) a b.
(Backend b, Applicative f) =>
(a -> f b)
-> AnnotatedOrderByElement b a -> f (AnnotatedOrderByElement b b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
AnnotatedOrderByElement b (m a) -> m (AnnotatedOrderByElement b a)
forall (f :: * -> *) a.
Applicative f =>
AnnotatedOrderByElement b (f a) -> f (AnnotatedOrderByElement b a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> AnnotatedOrderByElement b a -> m (AnnotatedOrderByElement b b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> AnnotatedOrderByElement b a -> f (AnnotatedOrderByElement b b)
$ctraverse :: forall (b :: BackendType) (f :: * -> *) a b.
(Backend b, Applicative f) =>
(a -> f b)
-> AnnotatedOrderByElement b a -> f (AnnotatedOrderByElement b b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> AnnotatedOrderByElement b a -> f (AnnotatedOrderByElement b b)
$csequenceA :: forall (b :: BackendType) (f :: * -> *) a.
(Backend b, Applicative f) =>
AnnotatedOrderByElement b (f a) -> f (AnnotatedOrderByElement b a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
AnnotatedOrderByElement b (f a) -> f (AnnotatedOrderByElement b a)
$cmapM :: forall (b :: BackendType) (m :: * -> *) a b.
(Backend b, Monad m) =>
(a -> m b)
-> AnnotatedOrderByElement b a -> m (AnnotatedOrderByElement b b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> AnnotatedOrderByElement b a -> m (AnnotatedOrderByElement b b)
$csequence :: forall (b :: BackendType) (m :: * -> *) a.
(Backend b, Monad m) =>
AnnotatedOrderByElement b (m a) -> m (AnnotatedOrderByElement b a)
sequence :: forall (m :: * -> *) a.
Monad m =>
AnnotatedOrderByElement b (m a) -> m (AnnotatedOrderByElement b a)
Traversable)
deriving stock instance
( Backend b,
Eq (AnnBoolExp b v),
Eq (AnnotatedAggregateOrderBy b v),
Eq (ComputedFieldOrderBy b v),
Eq (AnnRedactionExp b v)
) =>
Eq (AnnotatedOrderByElement b v)
deriving stock instance
( Backend b,
Show (AnnBoolExp b v),
Show (AnnotatedAggregateOrderBy b v),
Show (ComputedFieldOrderBy b v),
Show (AnnRedactionExp b v)
) =>
Show (AnnotatedOrderByElement b v)
instance
( Backend b,
Hashable (AnnBoolExp b v),
Hashable (AnnotatedAggregateOrderBy b v),
Hashable (ComputedFieldOrderBy b v),
Hashable (AnnRedactionExp b v)
) =>
Hashable (AnnotatedOrderByElement b v)
data AnnotatedAggregateOrderBy (b :: BackendType) v
= AAOCount
|
AAOOp (AggregateOrderByColumn b v)
deriving stock ((forall x.
AnnotatedAggregateOrderBy b v
-> Rep (AnnotatedAggregateOrderBy b v) x)
-> (forall x.
Rep (AnnotatedAggregateOrderBy b v) x
-> AnnotatedAggregateOrderBy b v)
-> Generic (AnnotatedAggregateOrderBy b v)
forall x.
Rep (AnnotatedAggregateOrderBy b v) x
-> AnnotatedAggregateOrderBy b v
forall x.
AnnotatedAggregateOrderBy b v
-> Rep (AnnotatedAggregateOrderBy b v) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) v x.
Rep (AnnotatedAggregateOrderBy b v) x
-> AnnotatedAggregateOrderBy b v
forall (b :: BackendType) v x.
AnnotatedAggregateOrderBy b v
-> Rep (AnnotatedAggregateOrderBy b v) x
$cfrom :: forall (b :: BackendType) v x.
AnnotatedAggregateOrderBy b v
-> Rep (AnnotatedAggregateOrderBy b v) x
from :: forall x.
AnnotatedAggregateOrderBy b v
-> Rep (AnnotatedAggregateOrderBy b v) x
$cto :: forall (b :: BackendType) v x.
Rep (AnnotatedAggregateOrderBy b v) x
-> AnnotatedAggregateOrderBy b v
to :: forall x.
Rep (AnnotatedAggregateOrderBy b v) x
-> AnnotatedAggregateOrderBy b v
Generic, (forall a b.
(a -> b)
-> AnnotatedAggregateOrderBy b a -> AnnotatedAggregateOrderBy b b)
-> (forall a b.
a
-> AnnotatedAggregateOrderBy b b -> AnnotatedAggregateOrderBy b a)
-> Functor (AnnotatedAggregateOrderBy b)
forall a b.
a -> AnnotatedAggregateOrderBy b b -> AnnotatedAggregateOrderBy b a
forall a b.
(a -> b)
-> AnnotatedAggregateOrderBy b a -> AnnotatedAggregateOrderBy b b
forall (b :: BackendType) a b.
Backend b =>
a -> AnnotatedAggregateOrderBy b b -> AnnotatedAggregateOrderBy b a
forall (b :: BackendType) a b.
Backend b =>
(a -> b)
-> AnnotatedAggregateOrderBy b a -> AnnotatedAggregateOrderBy b b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall (b :: BackendType) a b.
Backend b =>
(a -> b)
-> AnnotatedAggregateOrderBy b a -> AnnotatedAggregateOrderBy b b
fmap :: forall a b.
(a -> b)
-> AnnotatedAggregateOrderBy b a -> AnnotatedAggregateOrderBy b b
$c<$ :: forall (b :: BackendType) a b.
Backend b =>
a -> AnnotatedAggregateOrderBy b b -> AnnotatedAggregateOrderBy b a
<$ :: forall a b.
a -> AnnotatedAggregateOrderBy b b -> AnnotatedAggregateOrderBy b a
Functor, (forall m. Monoid m => AnnotatedAggregateOrderBy b m -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> AnnotatedAggregateOrderBy b a -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> AnnotatedAggregateOrderBy b a -> m)
-> (forall a b.
(a -> b -> b) -> b -> AnnotatedAggregateOrderBy b a -> b)
-> (forall a b.
(a -> b -> b) -> b -> AnnotatedAggregateOrderBy b a -> b)
-> (forall b a.
(b -> a -> b) -> b -> AnnotatedAggregateOrderBy b a -> b)
-> (forall b a.
(b -> a -> b) -> b -> AnnotatedAggregateOrderBy b a -> b)
-> (forall a. (a -> a -> a) -> AnnotatedAggregateOrderBy b a -> a)
-> (forall a. (a -> a -> a) -> AnnotatedAggregateOrderBy b a -> a)
-> (forall a. AnnotatedAggregateOrderBy b a -> [a])
-> (forall a. AnnotatedAggregateOrderBy b a -> Bool)
-> (forall a. AnnotatedAggregateOrderBy b a -> Int)
-> (forall a. Eq a => a -> AnnotatedAggregateOrderBy b a -> Bool)
-> (forall a. Ord a => AnnotatedAggregateOrderBy b a -> a)
-> (forall a. Ord a => AnnotatedAggregateOrderBy b a -> a)
-> (forall a. Num a => AnnotatedAggregateOrderBy b a -> a)
-> (forall a. Num a => AnnotatedAggregateOrderBy b a -> a)
-> Foldable (AnnotatedAggregateOrderBy b)
forall a. Eq a => a -> AnnotatedAggregateOrderBy b a -> Bool
forall a. Num a => AnnotatedAggregateOrderBy b a -> a
forall a. Ord a => AnnotatedAggregateOrderBy b a -> a
forall m. Monoid m => AnnotatedAggregateOrderBy b m -> m
forall a. AnnotatedAggregateOrderBy b a -> Bool
forall a. AnnotatedAggregateOrderBy b a -> Int
forall a. AnnotatedAggregateOrderBy b a -> [a]
forall a. (a -> a -> a) -> AnnotatedAggregateOrderBy b a -> a
forall m a.
Monoid m =>
(a -> m) -> AnnotatedAggregateOrderBy b a -> m
forall b a.
(b -> a -> b) -> b -> AnnotatedAggregateOrderBy b a -> b
forall a b.
(a -> b -> b) -> b -> AnnotatedAggregateOrderBy b a -> b
forall (b :: BackendType) a.
(Backend b, Eq a) =>
a -> AnnotatedAggregateOrderBy b a -> Bool
forall (b :: BackendType) a.
(Backend b, Num a) =>
AnnotatedAggregateOrderBy b a -> a
forall (b :: BackendType) a.
(Backend b, Ord a) =>
AnnotatedAggregateOrderBy b a -> a
forall (b :: BackendType) m.
(Backend b, Monoid m) =>
AnnotatedAggregateOrderBy b m -> m
forall (b :: BackendType) a.
Backend b =>
AnnotatedAggregateOrderBy b a -> Bool
forall (b :: BackendType) a.
Backend b =>
AnnotatedAggregateOrderBy b a -> Int
forall (b :: BackendType) a.
Backend b =>
AnnotatedAggregateOrderBy b a -> [a]
forall (b :: BackendType) a.
Backend b =>
(a -> a -> a) -> AnnotatedAggregateOrderBy b a -> a
forall (b :: BackendType) m a.
(Backend b, Monoid m) =>
(a -> m) -> AnnotatedAggregateOrderBy b a -> m
forall (b :: BackendType) b a.
Backend b =>
(b -> a -> b) -> b -> AnnotatedAggregateOrderBy b a -> b
forall (b :: BackendType) a b.
Backend b =>
(a -> b -> b) -> b -> AnnotatedAggregateOrderBy b a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall (b :: BackendType) m.
(Backend b, Monoid m) =>
AnnotatedAggregateOrderBy b m -> m
fold :: forall m. Monoid m => AnnotatedAggregateOrderBy b m -> m
$cfoldMap :: forall (b :: BackendType) m a.
(Backend b, Monoid m) =>
(a -> m) -> AnnotatedAggregateOrderBy b a -> m
foldMap :: forall m a.
Monoid m =>
(a -> m) -> AnnotatedAggregateOrderBy b a -> m
$cfoldMap' :: forall (b :: BackendType) m a.
(Backend b, Monoid m) =>
(a -> m) -> AnnotatedAggregateOrderBy b a -> m
foldMap' :: forall m a.
Monoid m =>
(a -> m) -> AnnotatedAggregateOrderBy b a -> m
$cfoldr :: forall (b :: BackendType) a b.
Backend b =>
(a -> b -> b) -> b -> AnnotatedAggregateOrderBy b a -> b
foldr :: forall a b.
(a -> b -> b) -> b -> AnnotatedAggregateOrderBy b a -> b
$cfoldr' :: forall (b :: BackendType) a b.
Backend b =>
(a -> b -> b) -> b -> AnnotatedAggregateOrderBy b a -> b
foldr' :: forall a b.
(a -> b -> b) -> b -> AnnotatedAggregateOrderBy b a -> b
$cfoldl :: forall (b :: BackendType) b a.
Backend b =>
(b -> a -> b) -> b -> AnnotatedAggregateOrderBy b a -> b
foldl :: forall b a.
(b -> a -> b) -> b -> AnnotatedAggregateOrderBy b a -> b
$cfoldl' :: forall (b :: BackendType) b a.
Backend b =>
(b -> a -> b) -> b -> AnnotatedAggregateOrderBy b a -> b
foldl' :: forall b a.
(b -> a -> b) -> b -> AnnotatedAggregateOrderBy b a -> b
$cfoldr1 :: forall (b :: BackendType) a.
Backend b =>
(a -> a -> a) -> AnnotatedAggregateOrderBy b a -> a
foldr1 :: forall a. (a -> a -> a) -> AnnotatedAggregateOrderBy b a -> a
$cfoldl1 :: forall (b :: BackendType) a.
Backend b =>
(a -> a -> a) -> AnnotatedAggregateOrderBy b a -> a
foldl1 :: forall a. (a -> a -> a) -> AnnotatedAggregateOrderBy b a -> a
$ctoList :: forall (b :: BackendType) a.
Backend b =>
AnnotatedAggregateOrderBy b a -> [a]
toList :: forall a. AnnotatedAggregateOrderBy b a -> [a]
$cnull :: forall (b :: BackendType) a.
Backend b =>
AnnotatedAggregateOrderBy b a -> Bool
null :: forall a. AnnotatedAggregateOrderBy b a -> Bool
$clength :: forall (b :: BackendType) a.
Backend b =>
AnnotatedAggregateOrderBy b a -> Int
length :: forall a. AnnotatedAggregateOrderBy b a -> Int
$celem :: forall (b :: BackendType) a.
(Backend b, Eq a) =>
a -> AnnotatedAggregateOrderBy b a -> Bool
elem :: forall a. Eq a => a -> AnnotatedAggregateOrderBy b a -> Bool
$cmaximum :: forall (b :: BackendType) a.
(Backend b, Ord a) =>
AnnotatedAggregateOrderBy b a -> a
maximum :: forall a. Ord a => AnnotatedAggregateOrderBy b a -> a
$cminimum :: forall (b :: BackendType) a.
(Backend b, Ord a) =>
AnnotatedAggregateOrderBy b a -> a
minimum :: forall a. Ord a => AnnotatedAggregateOrderBy b a -> a
$csum :: forall (b :: BackendType) a.
(Backend b, Num a) =>
AnnotatedAggregateOrderBy b a -> a
sum :: forall a. Num a => AnnotatedAggregateOrderBy b a -> a
$cproduct :: forall (b :: BackendType) a.
(Backend b, Num a) =>
AnnotatedAggregateOrderBy b a -> a
product :: forall a. Num a => AnnotatedAggregateOrderBy b a -> a
Foldable, Functor (AnnotatedAggregateOrderBy b)
Foldable (AnnotatedAggregateOrderBy b)
Functor (AnnotatedAggregateOrderBy b)
-> Foldable (AnnotatedAggregateOrderBy b)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> AnnotatedAggregateOrderBy b a
-> f (AnnotatedAggregateOrderBy b b))
-> (forall (f :: * -> *) a.
Applicative f =>
AnnotatedAggregateOrderBy b (f a)
-> f (AnnotatedAggregateOrderBy b a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> AnnotatedAggregateOrderBy b a
-> m (AnnotatedAggregateOrderBy b b))
-> (forall (m :: * -> *) a.
Monad m =>
AnnotatedAggregateOrderBy b (m a)
-> m (AnnotatedAggregateOrderBy b a))
-> Traversable (AnnotatedAggregateOrderBy b)
forall (b :: BackendType).
Backend b =>
Functor (AnnotatedAggregateOrderBy b)
forall (b :: BackendType).
Backend b =>
Foldable (AnnotatedAggregateOrderBy b)
forall (b :: BackendType) (m :: * -> *) a.
(Backend b, Monad m) =>
AnnotatedAggregateOrderBy b (m a)
-> m (AnnotatedAggregateOrderBy b a)
forall (b :: BackendType) (f :: * -> *) a.
(Backend b, Applicative f) =>
AnnotatedAggregateOrderBy b (f a)
-> f (AnnotatedAggregateOrderBy b a)
forall (b :: BackendType) (m :: * -> *) a b.
(Backend b, Monad m) =>
(a -> m b)
-> AnnotatedAggregateOrderBy b a
-> m (AnnotatedAggregateOrderBy b b)
forall (b :: BackendType) (f :: * -> *) a b.
(Backend b, Applicative f) =>
(a -> f b)
-> AnnotatedAggregateOrderBy b a
-> f (AnnotatedAggregateOrderBy b b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
AnnotatedAggregateOrderBy b (m a)
-> m (AnnotatedAggregateOrderBy b a)
forall (f :: * -> *) a.
Applicative f =>
AnnotatedAggregateOrderBy b (f a)
-> f (AnnotatedAggregateOrderBy b a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> AnnotatedAggregateOrderBy b a
-> m (AnnotatedAggregateOrderBy b b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> AnnotatedAggregateOrderBy b a
-> f (AnnotatedAggregateOrderBy b b)
$ctraverse :: forall (b :: BackendType) (f :: * -> *) a b.
(Backend b, Applicative f) =>
(a -> f b)
-> AnnotatedAggregateOrderBy b a
-> f (AnnotatedAggregateOrderBy b b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> AnnotatedAggregateOrderBy b a
-> f (AnnotatedAggregateOrderBy b b)
$csequenceA :: forall (b :: BackendType) (f :: * -> *) a.
(Backend b, Applicative f) =>
AnnotatedAggregateOrderBy b (f a)
-> f (AnnotatedAggregateOrderBy b a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
AnnotatedAggregateOrderBy b (f a)
-> f (AnnotatedAggregateOrderBy b a)
$cmapM :: forall (b :: BackendType) (m :: * -> *) a b.
(Backend b, Monad m) =>
(a -> m b)
-> AnnotatedAggregateOrderBy b a
-> m (AnnotatedAggregateOrderBy b b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> AnnotatedAggregateOrderBy b a
-> m (AnnotatedAggregateOrderBy b b)
$csequence :: forall (b :: BackendType) (m :: * -> *) a.
(Backend b, Monad m) =>
AnnotatedAggregateOrderBy b (m a)
-> m (AnnotatedAggregateOrderBy b a)
sequence :: forall (m :: * -> *) a.
Monad m =>
AnnotatedAggregateOrderBy b (m a)
-> m (AnnotatedAggregateOrderBy b a)
Traversable)
deriving stock instance (Backend b, Eq (AggregateOrderByColumn b v)) => Eq (AnnotatedAggregateOrderBy b v)
deriving stock instance (Backend b, Show (AggregateOrderByColumn b v)) => Show (AnnotatedAggregateOrderBy b v)
instance (Backend b, Hashable (AggregateOrderByColumn b v)) => Hashable (AnnotatedAggregateOrderBy b v)
data AggregateOrderByColumn b v = AggregateOrderByColumn
{ forall (b :: BackendType) v. AggregateOrderByColumn b v -> Text
_aobcAggregateFunctionName :: Text,
forall (b :: BackendType) v.
AggregateOrderByColumn b v -> ColumnType b
_aobcAggregateFunctionReturnType :: ColumnType b,
forall (b :: BackendType) v.
AggregateOrderByColumn b v -> ColumnInfo b
_aobcColumn :: ColumnInfo b,
forall (b :: BackendType) v.
AggregateOrderByColumn b v -> AnnRedactionExp b v
_aobcRedactionExpression :: AnnRedactionExp b v
}
deriving stock ((forall x.
AggregateOrderByColumn b v -> Rep (AggregateOrderByColumn b v) x)
-> (forall x.
Rep (AggregateOrderByColumn b v) x -> AggregateOrderByColumn b v)
-> Generic (AggregateOrderByColumn b v)
forall x.
Rep (AggregateOrderByColumn b v) x -> AggregateOrderByColumn b v
forall x.
AggregateOrderByColumn b v -> Rep (AggregateOrderByColumn b v) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) v x.
Rep (AggregateOrderByColumn b v) x -> AggregateOrderByColumn b v
forall (b :: BackendType) v x.
AggregateOrderByColumn b v -> Rep (AggregateOrderByColumn b v) x
$cfrom :: forall (b :: BackendType) v x.
AggregateOrderByColumn b v -> Rep (AggregateOrderByColumn b v) x
from :: forall x.
AggregateOrderByColumn b v -> Rep (AggregateOrderByColumn b v) x
$cto :: forall (b :: BackendType) v x.
Rep (AggregateOrderByColumn b v) x -> AggregateOrderByColumn b v
to :: forall x.
Rep (AggregateOrderByColumn b v) x -> AggregateOrderByColumn b v
Generic, (forall a b.
(a -> b)
-> AggregateOrderByColumn b a -> AggregateOrderByColumn b b)
-> (forall a b.
a -> AggregateOrderByColumn b b -> AggregateOrderByColumn b a)
-> Functor (AggregateOrderByColumn b)
forall a b.
a -> AggregateOrderByColumn b b -> AggregateOrderByColumn b a
forall a b.
(a -> b)
-> AggregateOrderByColumn b a -> AggregateOrderByColumn b b
forall (b :: BackendType) a b.
Backend b =>
a -> AggregateOrderByColumn b b -> AggregateOrderByColumn b a
forall (b :: BackendType) a b.
Backend b =>
(a -> b)
-> AggregateOrderByColumn b a -> AggregateOrderByColumn b b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall (b :: BackendType) a b.
Backend b =>
(a -> b)
-> AggregateOrderByColumn b a -> AggregateOrderByColumn b b
fmap :: forall a b.
(a -> b)
-> AggregateOrderByColumn b a -> AggregateOrderByColumn b b
$c<$ :: forall (b :: BackendType) a b.
Backend b =>
a -> AggregateOrderByColumn b b -> AggregateOrderByColumn b a
<$ :: forall a b.
a -> AggregateOrderByColumn b b -> AggregateOrderByColumn b a
Functor, (forall m. Monoid m => AggregateOrderByColumn b m -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> AggregateOrderByColumn b a -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> AggregateOrderByColumn b a -> m)
-> (forall a b.
(a -> b -> b) -> b -> AggregateOrderByColumn b a -> b)
-> (forall a b.
(a -> b -> b) -> b -> AggregateOrderByColumn b a -> b)
-> (forall b a.
(b -> a -> b) -> b -> AggregateOrderByColumn b a -> b)
-> (forall b a.
(b -> a -> b) -> b -> AggregateOrderByColumn b a -> b)
-> (forall a. (a -> a -> a) -> AggregateOrderByColumn b a -> a)
-> (forall a. (a -> a -> a) -> AggregateOrderByColumn b a -> a)
-> (forall a. AggregateOrderByColumn b a -> [a])
-> (forall a. AggregateOrderByColumn b a -> Bool)
-> (forall a. AggregateOrderByColumn b a -> Int)
-> (forall a. Eq a => a -> AggregateOrderByColumn b a -> Bool)
-> (forall a. Ord a => AggregateOrderByColumn b a -> a)
-> (forall a. Ord a => AggregateOrderByColumn b a -> a)
-> (forall a. Num a => AggregateOrderByColumn b a -> a)
-> (forall a. Num a => AggregateOrderByColumn b a -> a)
-> Foldable (AggregateOrderByColumn b)
forall a. Eq a => a -> AggregateOrderByColumn b a -> Bool
forall a. Num a => AggregateOrderByColumn b a -> a
forall a. Ord a => AggregateOrderByColumn b a -> a
forall m. Monoid m => AggregateOrderByColumn b m -> m
forall a. AggregateOrderByColumn b a -> Bool
forall a. AggregateOrderByColumn b a -> Int
forall a. AggregateOrderByColumn b a -> [a]
forall a. (a -> a -> a) -> AggregateOrderByColumn b a -> a
forall m a. Monoid m => (a -> m) -> AggregateOrderByColumn b a -> m
forall b a. (b -> a -> b) -> b -> AggregateOrderByColumn b a -> b
forall a b. (a -> b -> b) -> b -> AggregateOrderByColumn b a -> b
forall (b :: BackendType) a.
(Backend b, Eq a) =>
a -> AggregateOrderByColumn b a -> Bool
forall (b :: BackendType) a.
(Backend b, Num a) =>
AggregateOrderByColumn b a -> a
forall (b :: BackendType) a.
(Backend b, Ord a) =>
AggregateOrderByColumn b a -> a
forall (b :: BackendType) m.
(Backend b, Monoid m) =>
AggregateOrderByColumn b m -> m
forall (b :: BackendType) a.
Backend b =>
AggregateOrderByColumn b a -> Bool
forall (b :: BackendType) a.
Backend b =>
AggregateOrderByColumn b a -> Int
forall (b :: BackendType) a.
Backend b =>
AggregateOrderByColumn b a -> [a]
forall (b :: BackendType) a.
Backend b =>
(a -> a -> a) -> AggregateOrderByColumn b a -> a
forall (b :: BackendType) m a.
(Backend b, Monoid m) =>
(a -> m) -> AggregateOrderByColumn b a -> m
forall (b :: BackendType) b a.
Backend b =>
(b -> a -> b) -> b -> AggregateOrderByColumn b a -> b
forall (b :: BackendType) a b.
Backend b =>
(a -> b -> b) -> b -> AggregateOrderByColumn b a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall (b :: BackendType) m.
(Backend b, Monoid m) =>
AggregateOrderByColumn b m -> m
fold :: forall m. Monoid m => AggregateOrderByColumn b m -> m
$cfoldMap :: forall (b :: BackendType) m a.
(Backend b, Monoid m) =>
(a -> m) -> AggregateOrderByColumn b a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> AggregateOrderByColumn b a -> m
$cfoldMap' :: forall (b :: BackendType) m a.
(Backend b, Monoid m) =>
(a -> m) -> AggregateOrderByColumn b a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> AggregateOrderByColumn b a -> m
$cfoldr :: forall (b :: BackendType) a b.
Backend b =>
(a -> b -> b) -> b -> AggregateOrderByColumn b a -> b
foldr :: forall a b. (a -> b -> b) -> b -> AggregateOrderByColumn b a -> b
$cfoldr' :: forall (b :: BackendType) a b.
Backend b =>
(a -> b -> b) -> b -> AggregateOrderByColumn b a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> AggregateOrderByColumn b a -> b
$cfoldl :: forall (b :: BackendType) b a.
Backend b =>
(b -> a -> b) -> b -> AggregateOrderByColumn b a -> b
foldl :: forall b a. (b -> a -> b) -> b -> AggregateOrderByColumn b a -> b
$cfoldl' :: forall (b :: BackendType) b a.
Backend b =>
(b -> a -> b) -> b -> AggregateOrderByColumn b a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> AggregateOrderByColumn b a -> b
$cfoldr1 :: forall (b :: BackendType) a.
Backend b =>
(a -> a -> a) -> AggregateOrderByColumn b a -> a
foldr1 :: forall a. (a -> a -> a) -> AggregateOrderByColumn b a -> a
$cfoldl1 :: forall (b :: BackendType) a.
Backend b =>
(a -> a -> a) -> AggregateOrderByColumn b a -> a
foldl1 :: forall a. (a -> a -> a) -> AggregateOrderByColumn b a -> a
$ctoList :: forall (b :: BackendType) a.
Backend b =>
AggregateOrderByColumn b a -> [a]
toList :: forall a. AggregateOrderByColumn b a -> [a]
$cnull :: forall (b :: BackendType) a.
Backend b =>
AggregateOrderByColumn b a -> Bool
null :: forall a. AggregateOrderByColumn b a -> Bool
$clength :: forall (b :: BackendType) a.
Backend b =>
AggregateOrderByColumn b a -> Int
length :: forall a. AggregateOrderByColumn b a -> Int
$celem :: forall (b :: BackendType) a.
(Backend b, Eq a) =>
a -> AggregateOrderByColumn b a -> Bool
elem :: forall a. Eq a => a -> AggregateOrderByColumn b a -> Bool
$cmaximum :: forall (b :: BackendType) a.
(Backend b, Ord a) =>
AggregateOrderByColumn b a -> a
maximum :: forall a. Ord a => AggregateOrderByColumn b a -> a
$cminimum :: forall (b :: BackendType) a.
(Backend b, Ord a) =>
AggregateOrderByColumn b a -> a
minimum :: forall a. Ord a => AggregateOrderByColumn b a -> a
$csum :: forall (b :: BackendType) a.
(Backend b, Num a) =>
AggregateOrderByColumn b a -> a
sum :: forall a. Num a => AggregateOrderByColumn b a -> a
$cproduct :: forall (b :: BackendType) a.
(Backend b, Num a) =>
AggregateOrderByColumn b a -> a
product :: forall a. Num a => AggregateOrderByColumn b a -> a
Foldable, Functor (AggregateOrderByColumn b)
Foldable (AggregateOrderByColumn b)
Functor (AggregateOrderByColumn b)
-> Foldable (AggregateOrderByColumn b)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> AggregateOrderByColumn b a -> f (AggregateOrderByColumn b b))
-> (forall (f :: * -> *) a.
Applicative f =>
AggregateOrderByColumn b (f a) -> f (AggregateOrderByColumn b a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> AggregateOrderByColumn b a -> m (AggregateOrderByColumn b b))
-> (forall (m :: * -> *) a.
Monad m =>
AggregateOrderByColumn b (m a) -> m (AggregateOrderByColumn b a))
-> Traversable (AggregateOrderByColumn b)
forall (b :: BackendType).
Backend b =>
Functor (AggregateOrderByColumn b)
forall (b :: BackendType).
Backend b =>
Foldable (AggregateOrderByColumn b)
forall (b :: BackendType) (m :: * -> *) a.
(Backend b, Monad m) =>
AggregateOrderByColumn b (m a) -> m (AggregateOrderByColumn b a)
forall (b :: BackendType) (f :: * -> *) a.
(Backend b, Applicative f) =>
AggregateOrderByColumn b (f a) -> f (AggregateOrderByColumn b a)
forall (b :: BackendType) (m :: * -> *) a b.
(Backend b, Monad m) =>
(a -> m b)
-> AggregateOrderByColumn b a -> m (AggregateOrderByColumn b b)
forall (b :: BackendType) (f :: * -> *) a b.
(Backend b, Applicative f) =>
(a -> f b)
-> AggregateOrderByColumn b a -> f (AggregateOrderByColumn b b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
AggregateOrderByColumn b (m a) -> m (AggregateOrderByColumn b a)
forall (f :: * -> *) a.
Applicative f =>
AggregateOrderByColumn b (f a) -> f (AggregateOrderByColumn b a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> AggregateOrderByColumn b a -> m (AggregateOrderByColumn b b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> AggregateOrderByColumn b a -> f (AggregateOrderByColumn b b)
$ctraverse :: forall (b :: BackendType) (f :: * -> *) a b.
(Backend b, Applicative f) =>
(a -> f b)
-> AggregateOrderByColumn b a -> f (AggregateOrderByColumn b b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> AggregateOrderByColumn b a -> f (AggregateOrderByColumn b b)
$csequenceA :: forall (b :: BackendType) (f :: * -> *) a.
(Backend b, Applicative f) =>
AggregateOrderByColumn b (f a) -> f (AggregateOrderByColumn b a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
AggregateOrderByColumn b (f a) -> f (AggregateOrderByColumn b a)
$cmapM :: forall (b :: BackendType) (m :: * -> *) a b.
(Backend b, Monad m) =>
(a -> m b)
-> AggregateOrderByColumn b a -> m (AggregateOrderByColumn b b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> AggregateOrderByColumn b a -> m (AggregateOrderByColumn b b)
$csequence :: forall (b :: BackendType) (m :: * -> *) a.
(Backend b, Monad m) =>
AggregateOrderByColumn b (m a) -> m (AggregateOrderByColumn b a)
sequence :: forall (m :: * -> *) a.
Monad m =>
AggregateOrderByColumn b (m a) -> m (AggregateOrderByColumn b a)
Traversable)
deriving stock instance (Backend b, Eq (AnnRedactionExp b v)) => Eq (AggregateOrderByColumn b v)
deriving stock instance (Backend b, Show (AnnRedactionExp b v)) => Show (AggregateOrderByColumn b v)
instance (Backend b, Hashable (AnnRedactionExp b v)) => Hashable (AggregateOrderByColumn b v)
type AnnotatedOrderByItemG b v = OrderByItemG b (AnnotatedOrderByElement b v)
type AnnotatedOrderByItem b = AnnotatedOrderByItemG b (SQLExpression b)
data ComputedFieldOrderByElement (b :: BackendType) v
=
CFOBEScalar
(ScalarType b)
(AnnRedactionExp b v)
| CFOBETableAggregation
(TableName b)
(AnnBoolExp b v)
(AnnotatedAggregateOrderBy b v)
deriving stock ((forall x.
ComputedFieldOrderByElement b v
-> Rep (ComputedFieldOrderByElement b v) x)
-> (forall x.
Rep (ComputedFieldOrderByElement b v) x
-> ComputedFieldOrderByElement b v)
-> Generic (ComputedFieldOrderByElement b v)
forall x.
Rep (ComputedFieldOrderByElement b v) x
-> ComputedFieldOrderByElement b v
forall x.
ComputedFieldOrderByElement b v
-> Rep (ComputedFieldOrderByElement b v) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) v x.
Rep (ComputedFieldOrderByElement b v) x
-> ComputedFieldOrderByElement b v
forall (b :: BackendType) v x.
ComputedFieldOrderByElement b v
-> Rep (ComputedFieldOrderByElement b v) x
$cfrom :: forall (b :: BackendType) v x.
ComputedFieldOrderByElement b v
-> Rep (ComputedFieldOrderByElement b v) x
from :: forall x.
ComputedFieldOrderByElement b v
-> Rep (ComputedFieldOrderByElement b v) x
$cto :: forall (b :: BackendType) v x.
Rep (ComputedFieldOrderByElement b v) x
-> ComputedFieldOrderByElement b v
to :: forall x.
Rep (ComputedFieldOrderByElement b v) x
-> ComputedFieldOrderByElement b v
Generic, (forall a b.
(a -> b)
-> ComputedFieldOrderByElement b a
-> ComputedFieldOrderByElement b b)
-> (forall a b.
a
-> ComputedFieldOrderByElement b b
-> ComputedFieldOrderByElement b a)
-> Functor (ComputedFieldOrderByElement b)
forall a b.
a
-> ComputedFieldOrderByElement b b
-> ComputedFieldOrderByElement b a
forall a b.
(a -> b)
-> ComputedFieldOrderByElement b a
-> ComputedFieldOrderByElement b b
forall (b :: BackendType) a b.
Backend b =>
a
-> ComputedFieldOrderByElement b b
-> ComputedFieldOrderByElement b a
forall (b :: BackendType) a b.
Backend b =>
(a -> b)
-> ComputedFieldOrderByElement b a
-> ComputedFieldOrderByElement b b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall (b :: BackendType) a b.
Backend b =>
(a -> b)
-> ComputedFieldOrderByElement b a
-> ComputedFieldOrderByElement b b
fmap :: forall a b.
(a -> b)
-> ComputedFieldOrderByElement b a
-> ComputedFieldOrderByElement b b
$c<$ :: forall (b :: BackendType) a b.
Backend b =>
a
-> ComputedFieldOrderByElement b b
-> ComputedFieldOrderByElement b a
<$ :: forall a b.
a
-> ComputedFieldOrderByElement b b
-> ComputedFieldOrderByElement b a
Functor, (forall m. Monoid m => ComputedFieldOrderByElement b m -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> ComputedFieldOrderByElement b a -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> ComputedFieldOrderByElement b a -> m)
-> (forall a b.
(a -> b -> b) -> b -> ComputedFieldOrderByElement b a -> b)
-> (forall a b.
(a -> b -> b) -> b -> ComputedFieldOrderByElement b a -> b)
-> (forall b a.
(b -> a -> b) -> b -> ComputedFieldOrderByElement b a -> b)
-> (forall b a.
(b -> a -> b) -> b -> ComputedFieldOrderByElement b a -> b)
-> (forall a.
(a -> a -> a) -> ComputedFieldOrderByElement b a -> a)
-> (forall a.
(a -> a -> a) -> ComputedFieldOrderByElement b a -> a)
-> (forall a. ComputedFieldOrderByElement b a -> [a])
-> (forall a. ComputedFieldOrderByElement b a -> Bool)
-> (forall a. ComputedFieldOrderByElement b a -> Int)
-> (forall a. Eq a => a -> ComputedFieldOrderByElement b a -> Bool)
-> (forall a. Ord a => ComputedFieldOrderByElement b a -> a)
-> (forall a. Ord a => ComputedFieldOrderByElement b a -> a)
-> (forall a. Num a => ComputedFieldOrderByElement b a -> a)
-> (forall a. Num a => ComputedFieldOrderByElement b a -> a)
-> Foldable (ComputedFieldOrderByElement b)
forall a. Eq a => a -> ComputedFieldOrderByElement b a -> Bool
forall a. Num a => ComputedFieldOrderByElement b a -> a
forall a. Ord a => ComputedFieldOrderByElement b a -> a
forall m. Monoid m => ComputedFieldOrderByElement b m -> m
forall a. ComputedFieldOrderByElement b a -> Bool
forall a. ComputedFieldOrderByElement b a -> Int
forall a. ComputedFieldOrderByElement b a -> [a]
forall a. (a -> a -> a) -> ComputedFieldOrderByElement b a -> a
forall m a.
Monoid m =>
(a -> m) -> ComputedFieldOrderByElement b a -> m
forall b a.
(b -> a -> b) -> b -> ComputedFieldOrderByElement b a -> b
forall a b.
(a -> b -> b) -> b -> ComputedFieldOrderByElement b a -> b
forall (b :: BackendType) a.
(Backend b, Eq a) =>
a -> ComputedFieldOrderByElement b a -> Bool
forall (b :: BackendType) a.
(Backend b, Num a) =>
ComputedFieldOrderByElement b a -> a
forall (b :: BackendType) a.
(Backend b, Ord a) =>
ComputedFieldOrderByElement b a -> a
forall (b :: BackendType) m.
(Backend b, Monoid m) =>
ComputedFieldOrderByElement b m -> m
forall (b :: BackendType) a.
Backend b =>
ComputedFieldOrderByElement b a -> Bool
forall (b :: BackendType) a.
Backend b =>
ComputedFieldOrderByElement b a -> Int
forall (b :: BackendType) a.
Backend b =>
ComputedFieldOrderByElement b a -> [a]
forall (b :: BackendType) a.
Backend b =>
(a -> a -> a) -> ComputedFieldOrderByElement b a -> a
forall (b :: BackendType) m a.
(Backend b, Monoid m) =>
(a -> m) -> ComputedFieldOrderByElement b a -> m
forall (b :: BackendType) b a.
Backend b =>
(b -> a -> b) -> b -> ComputedFieldOrderByElement b a -> b
forall (b :: BackendType) a b.
Backend b =>
(a -> b -> b) -> b -> ComputedFieldOrderByElement b a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall (b :: BackendType) m.
(Backend b, Monoid m) =>
ComputedFieldOrderByElement b m -> m
fold :: forall m. Monoid m => ComputedFieldOrderByElement b m -> m
$cfoldMap :: forall (b :: BackendType) m a.
(Backend b, Monoid m) =>
(a -> m) -> ComputedFieldOrderByElement b a -> m
foldMap :: forall m a.
Monoid m =>
(a -> m) -> ComputedFieldOrderByElement b a -> m
$cfoldMap' :: forall (b :: BackendType) m a.
(Backend b, Monoid m) =>
(a -> m) -> ComputedFieldOrderByElement b a -> m
foldMap' :: forall m a.
Monoid m =>
(a -> m) -> ComputedFieldOrderByElement b a -> m
$cfoldr :: forall (b :: BackendType) a b.
Backend b =>
(a -> b -> b) -> b -> ComputedFieldOrderByElement b a -> b
foldr :: forall a b.
(a -> b -> b) -> b -> ComputedFieldOrderByElement b a -> b
$cfoldr' :: forall (b :: BackendType) a b.
Backend b =>
(a -> b -> b) -> b -> ComputedFieldOrderByElement b a -> b
foldr' :: forall a b.
(a -> b -> b) -> b -> ComputedFieldOrderByElement b a -> b
$cfoldl :: forall (b :: BackendType) b a.
Backend b =>
(b -> a -> b) -> b -> ComputedFieldOrderByElement b a -> b
foldl :: forall b a.
(b -> a -> b) -> b -> ComputedFieldOrderByElement b a -> b
$cfoldl' :: forall (b :: BackendType) b a.
Backend b =>
(b -> a -> b) -> b -> ComputedFieldOrderByElement b a -> b
foldl' :: forall b a.
(b -> a -> b) -> b -> ComputedFieldOrderByElement b a -> b
$cfoldr1 :: forall (b :: BackendType) a.
Backend b =>
(a -> a -> a) -> ComputedFieldOrderByElement b a -> a
foldr1 :: forall a. (a -> a -> a) -> ComputedFieldOrderByElement b a -> a
$cfoldl1 :: forall (b :: BackendType) a.
Backend b =>
(a -> a -> a) -> ComputedFieldOrderByElement b a -> a
foldl1 :: forall a. (a -> a -> a) -> ComputedFieldOrderByElement b a -> a
$ctoList :: forall (b :: BackendType) a.
Backend b =>
ComputedFieldOrderByElement b a -> [a]
toList :: forall a. ComputedFieldOrderByElement b a -> [a]
$cnull :: forall (b :: BackendType) a.
Backend b =>
ComputedFieldOrderByElement b a -> Bool
null :: forall a. ComputedFieldOrderByElement b a -> Bool
$clength :: forall (b :: BackendType) a.
Backend b =>
ComputedFieldOrderByElement b a -> Int
length :: forall a. ComputedFieldOrderByElement b a -> Int
$celem :: forall (b :: BackendType) a.
(Backend b, Eq a) =>
a -> ComputedFieldOrderByElement b a -> Bool
elem :: forall a. Eq a => a -> ComputedFieldOrderByElement b a -> Bool
$cmaximum :: forall (b :: BackendType) a.
(Backend b, Ord a) =>
ComputedFieldOrderByElement b a -> a
maximum :: forall a. Ord a => ComputedFieldOrderByElement b a -> a
$cminimum :: forall (b :: BackendType) a.
(Backend b, Ord a) =>
ComputedFieldOrderByElement b a -> a
minimum :: forall a. Ord a => ComputedFieldOrderByElement b a -> a
$csum :: forall (b :: BackendType) a.
(Backend b, Num a) =>
ComputedFieldOrderByElement b a -> a
sum :: forall a. Num a => ComputedFieldOrderByElement b a -> a
$cproduct :: forall (b :: BackendType) a.
(Backend b, Num a) =>
ComputedFieldOrderByElement b a -> a
product :: forall a. Num a => ComputedFieldOrderByElement b a -> a
Foldable, Functor (ComputedFieldOrderByElement b)
Foldable (ComputedFieldOrderByElement b)
Functor (ComputedFieldOrderByElement b)
-> Foldable (ComputedFieldOrderByElement b)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> ComputedFieldOrderByElement b a
-> f (ComputedFieldOrderByElement b b))
-> (forall (f :: * -> *) a.
Applicative f =>
ComputedFieldOrderByElement b (f a)
-> f (ComputedFieldOrderByElement b a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> ComputedFieldOrderByElement b a
-> m (ComputedFieldOrderByElement b b))
-> (forall (m :: * -> *) a.
Monad m =>
ComputedFieldOrderByElement b (m a)
-> m (ComputedFieldOrderByElement b a))
-> Traversable (ComputedFieldOrderByElement b)
forall (b :: BackendType).
Backend b =>
Functor (ComputedFieldOrderByElement b)
forall (b :: BackendType).
Backend b =>
Foldable (ComputedFieldOrderByElement b)
forall (b :: BackendType) (m :: * -> *) a.
(Backend b, Monad m) =>
ComputedFieldOrderByElement b (m a)
-> m (ComputedFieldOrderByElement b a)
forall (b :: BackendType) (f :: * -> *) a.
(Backend b, Applicative f) =>
ComputedFieldOrderByElement b (f a)
-> f (ComputedFieldOrderByElement b a)
forall (b :: BackendType) (m :: * -> *) a b.
(Backend b, Monad m) =>
(a -> m b)
-> ComputedFieldOrderByElement b a
-> m (ComputedFieldOrderByElement b b)
forall (b :: BackendType) (f :: * -> *) a b.
(Backend b, Applicative f) =>
(a -> f b)
-> ComputedFieldOrderByElement b a
-> f (ComputedFieldOrderByElement b b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
ComputedFieldOrderByElement b (m a)
-> m (ComputedFieldOrderByElement b a)
forall (f :: * -> *) a.
Applicative f =>
ComputedFieldOrderByElement b (f a)
-> f (ComputedFieldOrderByElement b a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> ComputedFieldOrderByElement b a
-> m (ComputedFieldOrderByElement b b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> ComputedFieldOrderByElement b a
-> f (ComputedFieldOrderByElement b b)
$ctraverse :: forall (b :: BackendType) (f :: * -> *) a b.
(Backend b, Applicative f) =>
(a -> f b)
-> ComputedFieldOrderByElement b a
-> f (ComputedFieldOrderByElement b b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> ComputedFieldOrderByElement b a
-> f (ComputedFieldOrderByElement b b)
$csequenceA :: forall (b :: BackendType) (f :: * -> *) a.
(Backend b, Applicative f) =>
ComputedFieldOrderByElement b (f a)
-> f (ComputedFieldOrderByElement b a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
ComputedFieldOrderByElement b (f a)
-> f (ComputedFieldOrderByElement b a)
$cmapM :: forall (b :: BackendType) (m :: * -> *) a b.
(Backend b, Monad m) =>
(a -> m b)
-> ComputedFieldOrderByElement b a
-> m (ComputedFieldOrderByElement b b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> ComputedFieldOrderByElement b a
-> m (ComputedFieldOrderByElement b b)
$csequence :: forall (b :: BackendType) (m :: * -> *) a.
(Backend b, Monad m) =>
ComputedFieldOrderByElement b (m a)
-> m (ComputedFieldOrderByElement b a)
sequence :: forall (m :: * -> *) a.
Monad m =>
ComputedFieldOrderByElement b (m a)
-> m (ComputedFieldOrderByElement b a)
Traversable)
deriving stock instance
( Backend b,
Eq (AnnBoolExp b v),
Eq (AnnotatedAggregateOrderBy b v),
Eq (AnnRedactionExp b v)
) =>
Eq (ComputedFieldOrderByElement b v)
deriving stock instance
( Backend b,
Show v,
Show (AnnBoolExp b v),
Show (AnnotatedAggregateOrderBy b v),
Show (AnnRedactionExp b v)
) =>
Show (ComputedFieldOrderByElement b v)
instance
( Backend b,
Hashable (AnnBoolExp b v),
Hashable (AnnotatedAggregateOrderBy b v),
Hashable (AnnRedactionExp b v)
) =>
Hashable (ComputedFieldOrderByElement b v)
data ComputedFieldOrderBy (b :: BackendType) v = ComputedFieldOrderBy
{ forall (b :: BackendType) v.
ComputedFieldOrderBy b v -> XComputedField b
_cfobXField :: XComputedField b,
forall (b :: BackendType) v.
ComputedFieldOrderBy b v -> ComputedFieldName
_cfobName :: ComputedFieldName,
forall (b :: BackendType) v.
ComputedFieldOrderBy b v -> FunctionName b
_cfobFunction :: FunctionName b,
forall (b :: BackendType) v.
ComputedFieldOrderBy b v -> FunctionArgsExp b v
_cfobFunctionArgsExp :: FunctionArgsExp b v,
forall (b :: BackendType) v.
ComputedFieldOrderBy b v -> ComputedFieldOrderByElement b v
_cfobOrderByElement :: ComputedFieldOrderByElement b v
}
deriving stock ((forall x.
ComputedFieldOrderBy b v -> Rep (ComputedFieldOrderBy b v) x)
-> (forall x.
Rep (ComputedFieldOrderBy b v) x -> ComputedFieldOrderBy b v)
-> Generic (ComputedFieldOrderBy b v)
forall x.
Rep (ComputedFieldOrderBy b v) x -> ComputedFieldOrderBy b v
forall x.
ComputedFieldOrderBy b v -> Rep (ComputedFieldOrderBy b v) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) v x.
Rep (ComputedFieldOrderBy b v) x -> ComputedFieldOrderBy b v
forall (b :: BackendType) v x.
ComputedFieldOrderBy b v -> Rep (ComputedFieldOrderBy b v) x
$cfrom :: forall (b :: BackendType) v x.
ComputedFieldOrderBy b v -> Rep (ComputedFieldOrderBy b v) x
from :: forall x.
ComputedFieldOrderBy b v -> Rep (ComputedFieldOrderBy b v) x
$cto :: forall (b :: BackendType) v x.
Rep (ComputedFieldOrderBy b v) x -> ComputedFieldOrderBy b v
to :: forall x.
Rep (ComputedFieldOrderBy b v) x -> ComputedFieldOrderBy b v
Generic)
deriving stock instance (Backend b) => Functor (ComputedFieldOrderBy b)
deriving stock instance (Backend b) => Foldable (ComputedFieldOrderBy b)
deriving stock instance (Backend b) => Traversable (ComputedFieldOrderBy b)
deriving stock instance
( Backend b,
Eq (ComputedFieldOrderByElement b v),
Eq (FunctionArgsExp b v)
) =>
Eq (ComputedFieldOrderBy b v)
deriving stock instance
( Backend b,
Show (ComputedFieldOrderByElement b v),
Show (FunctionArgsExp b v)
) =>
Show (ComputedFieldOrderBy b v)
instance
( Backend b,
Hashable (ComputedFieldOrderByElement b v),
Hashable (FunctionArgsExp b v)
) =>
Hashable (ComputedFieldOrderBy b v)