module Hasura.RQL.IR.OrderBy
  ( OrderByCol (..),
    OrderByItemG (..),
    OrderByItem,
    -- used by RQL.DML.Types
    orderByColFromTxt,
  )
where

import Data.Aeson
import Data.Text qualified as T
import Hasura.Prelude
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.BackendType
import Hasura.RQL.Types.Common

-- order by col

data OrderByCol
  = OCPG FieldName
  | OCRel FieldName OrderByCol
  deriving (Int -> OrderByCol -> ShowS
[OrderByCol] -> ShowS
OrderByCol -> String
(Int -> OrderByCol -> ShowS)
-> (OrderByCol -> String)
-> ([OrderByCol] -> ShowS)
-> Show OrderByCol
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OrderByCol -> ShowS
showsPrec :: Int -> OrderByCol -> ShowS
$cshow :: OrderByCol -> String
show :: OrderByCol -> String
$cshowList :: [OrderByCol] -> ShowS
showList :: [OrderByCol] -> ShowS
Show, OrderByCol -> OrderByCol -> Bool
(OrderByCol -> OrderByCol -> Bool)
-> (OrderByCol -> OrderByCol -> Bool) -> Eq OrderByCol
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OrderByCol -> OrderByCol -> Bool
== :: OrderByCol -> OrderByCol -> Bool
$c/= :: OrderByCol -> OrderByCol -> Bool
/= :: OrderByCol -> OrderByCol -> Bool
Eq)

instance FromJSON OrderByCol where
  parseJSON :: Value -> Parser OrderByCol
parseJSON = \case
    (String Text
t) -> [Text] -> Parser OrderByCol
forall (m :: * -> *). MonadFail m => [Text] -> m OrderByCol
orderByColFromToks ([Text] -> Parser OrderByCol) -> [Text] -> Parser OrderByCol
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> [Text]
T.split (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.') Text
t
    Value
v -> Value -> Parser [Text]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Text] -> ([Text] -> Parser OrderByCol) -> Parser OrderByCol
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Text] -> Parser OrderByCol
forall (m :: * -> *). MonadFail m => [Text] -> m OrderByCol
orderByColFromToks

orderByColFromToks ::
  (MonadFail m) =>
  [Text] ->
  m OrderByCol
orderByColFromToks :: forall (m :: * -> *). MonadFail m => [Text] -> m OrderByCol
orderByColFromToks [Text]
toks = do
  Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ((Text -> Bool) -> [Text] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Text -> Bool
T.null [Text]
toks) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ String -> m ()
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"col/rel cannot be empty"
  case [Text]
toks of
    [] -> String -> m OrderByCol
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"failed to parse an OrderByCol: found empty cols"
    Text
x : [Text]
xs -> OrderByCol -> m OrderByCol
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (OrderByCol -> m OrderByCol) -> OrderByCol -> m OrderByCol
forall a b. (a -> b) -> a -> b
$ FieldName -> [Text] -> OrderByCol
go (Text -> FieldName
FieldName Text
x) [Text]
xs
  where
    go :: FieldName -> [Text] -> OrderByCol
go FieldName
fld = \case
      [] -> FieldName -> OrderByCol
OCPG FieldName
fld
      Text
x : [Text]
xs -> FieldName -> OrderByCol -> OrderByCol
OCRel FieldName
fld (OrderByCol -> OrderByCol) -> OrderByCol -> OrderByCol
forall a b. (a -> b) -> a -> b
$ FieldName -> [Text] -> OrderByCol
go (Text -> FieldName
FieldName Text
x) [Text]
xs

orderByColFromTxt ::
  (MonadFail m) =>
  Text ->
  m OrderByCol
orderByColFromTxt :: forall (m :: * -> *). MonadFail m => Text -> m OrderByCol
orderByColFromTxt =
  [Text] -> m OrderByCol
forall (m :: * -> *). MonadFail m => [Text] -> m OrderByCol
orderByColFromToks ([Text] -> m OrderByCol)
-> (Text -> [Text]) -> Text -> m OrderByCol
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> [Text]
T.split (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.')

-- order by item

data OrderByItemG (b :: BackendType) a = OrderByItemG
  { forall (b :: BackendType) a.
OrderByItemG b a -> Maybe (BasicOrderType b)
obiType :: Maybe (BasicOrderType b),
    forall (b :: BackendType) a. OrderByItemG b a -> a
obiColumn :: a,
    forall (b :: BackendType) a.
OrderByItemG b a -> Maybe (NullsOrderType b)
obiNulls :: Maybe (NullsOrderType b)
  }
  deriving ((forall a b. (a -> b) -> OrderByItemG b a -> OrderByItemG b b)
-> (forall a b. a -> OrderByItemG b b -> OrderByItemG b a)
-> Functor (OrderByItemG b)
forall a b. a -> OrderByItemG b b -> OrderByItemG b a
forall a b. (a -> b) -> OrderByItemG b a -> OrderByItemG b b
forall (b :: BackendType) a b.
a -> OrderByItemG b b -> OrderByItemG b a
forall (b :: BackendType) a b.
(a -> b) -> OrderByItemG b a -> OrderByItemG 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.
(a -> b) -> OrderByItemG b a -> OrderByItemG b b
fmap :: forall a b. (a -> b) -> OrderByItemG b a -> OrderByItemG b b
$c<$ :: forall (b :: BackendType) a b.
a -> OrderByItemG b b -> OrderByItemG b a
<$ :: forall a b. a -> OrderByItemG b b -> OrderByItemG b a
Functor, (forall m. Monoid m => OrderByItemG b m -> m)
-> (forall m a. Monoid m => (a -> m) -> OrderByItemG b a -> m)
-> (forall m a. Monoid m => (a -> m) -> OrderByItemG b a -> m)
-> (forall a b. (a -> b -> b) -> b -> OrderByItemG b a -> b)
-> (forall a b. (a -> b -> b) -> b -> OrderByItemG b a -> b)
-> (forall b a. (b -> a -> b) -> b -> OrderByItemG b a -> b)
-> (forall b a. (b -> a -> b) -> b -> OrderByItemG b a -> b)
-> (forall a. (a -> a -> a) -> OrderByItemG b a -> a)
-> (forall a. (a -> a -> a) -> OrderByItemG b a -> a)
-> (forall a. OrderByItemG b a -> [a])
-> (forall a. OrderByItemG b a -> Bool)
-> (forall a. OrderByItemG b a -> Int)
-> (forall a. Eq a => a -> OrderByItemG b a -> Bool)
-> (forall a. Ord a => OrderByItemG b a -> a)
-> (forall a. Ord a => OrderByItemG b a -> a)
-> (forall a. Num a => OrderByItemG b a -> a)
-> (forall a. Num a => OrderByItemG b a -> a)
-> Foldable (OrderByItemG b)
forall a. Eq a => a -> OrderByItemG b a -> Bool
forall a. Num a => OrderByItemG b a -> a
forall a. Ord a => OrderByItemG b a -> a
forall m. Monoid m => OrderByItemG b m -> m
forall a. OrderByItemG b a -> Bool
forall a. OrderByItemG b a -> Int
forall a. OrderByItemG b a -> [a]
forall a. (a -> a -> a) -> OrderByItemG b a -> a
forall m a. Monoid m => (a -> m) -> OrderByItemG b a -> m
forall b a. (b -> a -> b) -> b -> OrderByItemG b a -> b
forall a b. (a -> b -> b) -> b -> OrderByItemG b a -> b
forall (b :: BackendType) a. Eq a => a -> OrderByItemG b a -> Bool
forall (b :: BackendType) a. Num a => OrderByItemG b a -> a
forall (b :: BackendType) a. Ord a => OrderByItemG b a -> a
forall (b :: BackendType) m. Monoid m => OrderByItemG b m -> m
forall (b :: BackendType) a. OrderByItemG b a -> Bool
forall (b :: BackendType) a. OrderByItemG b a -> Int
forall (b :: BackendType) a. OrderByItemG b a -> [a]
forall (b :: BackendType) a. (a -> a -> a) -> OrderByItemG b a -> a
forall (b :: BackendType) m a.
Monoid m =>
(a -> m) -> OrderByItemG b a -> m
forall (b :: BackendType) b a.
(b -> a -> b) -> b -> OrderByItemG b a -> b
forall (b :: BackendType) a b.
(a -> b -> b) -> b -> OrderByItemG 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. Monoid m => OrderByItemG b m -> m
fold :: forall m. Monoid m => OrderByItemG b m -> m
$cfoldMap :: forall (b :: BackendType) m a.
Monoid m =>
(a -> m) -> OrderByItemG b a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> OrderByItemG b a -> m
$cfoldMap' :: forall (b :: BackendType) m a.
Monoid m =>
(a -> m) -> OrderByItemG b a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> OrderByItemG b a -> m
$cfoldr :: forall (b :: BackendType) a b.
(a -> b -> b) -> b -> OrderByItemG b a -> b
foldr :: forall a b. (a -> b -> b) -> b -> OrderByItemG b a -> b
$cfoldr' :: forall (b :: BackendType) a b.
(a -> b -> b) -> b -> OrderByItemG b a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> OrderByItemG b a -> b
$cfoldl :: forall (b :: BackendType) b a.
(b -> a -> b) -> b -> OrderByItemG b a -> b
foldl :: forall b a. (b -> a -> b) -> b -> OrderByItemG b a -> b
$cfoldl' :: forall (b :: BackendType) b a.
(b -> a -> b) -> b -> OrderByItemG b a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> OrderByItemG b a -> b
$cfoldr1 :: forall (b :: BackendType) a. (a -> a -> a) -> OrderByItemG b a -> a
foldr1 :: forall a. (a -> a -> a) -> OrderByItemG b a -> a
$cfoldl1 :: forall (b :: BackendType) a. (a -> a -> a) -> OrderByItemG b a -> a
foldl1 :: forall a. (a -> a -> a) -> OrderByItemG b a -> a
$ctoList :: forall (b :: BackendType) a. OrderByItemG b a -> [a]
toList :: forall a. OrderByItemG b a -> [a]
$cnull :: forall (b :: BackendType) a. OrderByItemG b a -> Bool
null :: forall a. OrderByItemG b a -> Bool
$clength :: forall (b :: BackendType) a. OrderByItemG b a -> Int
length :: forall a. OrderByItemG b a -> Int
$celem :: forall (b :: BackendType) a. Eq a => a -> OrderByItemG b a -> Bool
elem :: forall a. Eq a => a -> OrderByItemG b a -> Bool
$cmaximum :: forall (b :: BackendType) a. Ord a => OrderByItemG b a -> a
maximum :: forall a. Ord a => OrderByItemG b a -> a
$cminimum :: forall (b :: BackendType) a. Ord a => OrderByItemG b a -> a
minimum :: forall a. Ord a => OrderByItemG b a -> a
$csum :: forall (b :: BackendType) a. Num a => OrderByItemG b a -> a
sum :: forall a. Num a => OrderByItemG b a -> a
$cproduct :: forall (b :: BackendType) a. Num a => OrderByItemG b a -> a
product :: forall a. Num a => OrderByItemG b a -> a
Foldable, Functor (OrderByItemG b)
Foldable (OrderByItemG b)
Functor (OrderByItemG b)
-> Foldable (OrderByItemG b)
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> OrderByItemG b a -> f (OrderByItemG b b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    OrderByItemG b (f a) -> f (OrderByItemG b a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> OrderByItemG b a -> m (OrderByItemG b b))
-> (forall (m :: * -> *) a.
    Monad m =>
    OrderByItemG b (m a) -> m (OrderByItemG b a))
-> Traversable (OrderByItemG b)
forall (b :: BackendType). Functor (OrderByItemG b)
forall (b :: BackendType). Foldable (OrderByItemG b)
forall (b :: BackendType) (m :: * -> *) a.
Monad m =>
OrderByItemG b (m a) -> m (OrderByItemG b a)
forall (b :: BackendType) (f :: * -> *) a.
Applicative f =>
OrderByItemG b (f a) -> f (OrderByItemG b a)
forall (b :: BackendType) (m :: * -> *) a b.
Monad m =>
(a -> m b) -> OrderByItemG b a -> m (OrderByItemG b b)
forall (b :: BackendType) (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> OrderByItemG b a -> f (OrderByItemG 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 =>
OrderByItemG b (m a) -> m (OrderByItemG b a)
forall (f :: * -> *) a.
Applicative f =>
OrderByItemG b (f a) -> f (OrderByItemG b a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> OrderByItemG b a -> m (OrderByItemG b b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> OrderByItemG b a -> f (OrderByItemG b b)
$ctraverse :: forall (b :: BackendType) (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> OrderByItemG b a -> f (OrderByItemG b b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> OrderByItemG b a -> f (OrderByItemG b b)
$csequenceA :: forall (b :: BackendType) (f :: * -> *) a.
Applicative f =>
OrderByItemG b (f a) -> f (OrderByItemG b a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
OrderByItemG b (f a) -> f (OrderByItemG b a)
$cmapM :: forall (b :: BackendType) (m :: * -> *) a b.
Monad m =>
(a -> m b) -> OrderByItemG b a -> m (OrderByItemG b b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> OrderByItemG b a -> m (OrderByItemG b b)
$csequence :: forall (b :: BackendType) (m :: * -> *) a.
Monad m =>
OrderByItemG b (m a) -> m (OrderByItemG b a)
sequence :: forall (m :: * -> *) a.
Monad m =>
OrderByItemG b (m a) -> m (OrderByItemG b a)
Traversable, (forall x. OrderByItemG b a -> Rep (OrderByItemG b a) x)
-> (forall x. Rep (OrderByItemG b a) x -> OrderByItemG b a)
-> Generic (OrderByItemG b a)
forall x. Rep (OrderByItemG b a) x -> OrderByItemG b a
forall x. OrderByItemG b a -> Rep (OrderByItemG b a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) a x.
Rep (OrderByItemG b a) x -> OrderByItemG b a
forall (b :: BackendType) a x.
OrderByItemG b a -> Rep (OrderByItemG b a) x
$cfrom :: forall (b :: BackendType) a x.
OrderByItemG b a -> Rep (OrderByItemG b a) x
from :: forall x. OrderByItemG b a -> Rep (OrderByItemG b a) x
$cto :: forall (b :: BackendType) a x.
Rep (OrderByItemG b a) x -> OrderByItemG b a
to :: forall x. Rep (OrderByItemG b a) x -> OrderByItemG b a
Generic)

deriving instance (Backend b, Show a) => Show (OrderByItemG b a)

deriving instance (Backend b, Eq a) => Eq (OrderByItemG b a)

instance (Backend b, Hashable a) => Hashable (OrderByItemG b a)

type OrderByItem b = OrderByItemG b OrderByCol