module Hasura.Backends.DataConnector.IR.Query
( QueryRequest (..),
Query (..),
Field (..),
RelationshipField (..),
)
where
import Data.Aeson (ToJSON)
import Data.Aeson qualified as J
import Data.Aeson.Key qualified as Key
import Data.Aeson.KeyMap qualified as KeyMap
import Data.Bifunctor (bimap)
import Data.HashMap.Strict qualified as HashMap
import Hasura.Backends.DataConnector.API qualified as API
import Hasura.Backends.DataConnector.IR.Aggregate qualified as IR.A
import Hasura.Backends.DataConnector.IR.Column qualified as IR.C
import Hasura.Backends.DataConnector.IR.Expression qualified as IR.E
import Hasura.Backends.DataConnector.IR.OrderBy qualified as IR.O
import Hasura.Backends.DataConnector.IR.Relationships qualified as IR.R
import Hasura.Backends.DataConnector.IR.Table qualified as IR.T
import Hasura.Prelude
import Hasura.RQL.Types.Common (FieldName (..))
import Witch qualified
data QueryRequest = QueryRequest
{ QueryRequest -> Name
_qrTable :: IR.T.Name,
QueryRequest -> TableRelationships
_qrTableRelationships :: IR.R.TableRelationships,
QueryRequest -> Query
_qrQuery :: Query
}
deriving stock (Typeable QueryRequest
DataType
Constr
Typeable QueryRequest
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QueryRequest -> c QueryRequest)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QueryRequest)
-> (QueryRequest -> Constr)
-> (QueryRequest -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c QueryRequest))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c QueryRequest))
-> ((forall b. Data b => b -> b) -> QueryRequest -> QueryRequest)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QueryRequest -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QueryRequest -> r)
-> (forall u. (forall d. Data d => d -> u) -> QueryRequest -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> QueryRequest -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> QueryRequest -> m QueryRequest)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QueryRequest -> m QueryRequest)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QueryRequest -> m QueryRequest)
-> Data QueryRequest
QueryRequest -> DataType
QueryRequest -> Constr
(forall b. Data b => b -> b) -> QueryRequest -> QueryRequest
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QueryRequest -> c QueryRequest
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QueryRequest
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> QueryRequest -> u
forall u. (forall d. Data d => d -> u) -> QueryRequest -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QueryRequest -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QueryRequest -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> QueryRequest -> m QueryRequest
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QueryRequest -> m QueryRequest
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QueryRequest
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QueryRequest -> c QueryRequest
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c QueryRequest)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c QueryRequest)
$cQueryRequest :: Constr
$tQueryRequest :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> QueryRequest -> m QueryRequest
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QueryRequest -> m QueryRequest
gmapMp :: (forall d. Data d => d -> m d) -> QueryRequest -> m QueryRequest
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QueryRequest -> m QueryRequest
gmapM :: (forall d. Data d => d -> m d) -> QueryRequest -> m QueryRequest
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> QueryRequest -> m QueryRequest
gmapQi :: Int -> (forall d. Data d => d -> u) -> QueryRequest -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> QueryRequest -> u
gmapQ :: (forall d. Data d => d -> u) -> QueryRequest -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> QueryRequest -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QueryRequest -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QueryRequest -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QueryRequest -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QueryRequest -> r
gmapT :: (forall b. Data b => b -> b) -> QueryRequest -> QueryRequest
$cgmapT :: (forall b. Data b => b -> b) -> QueryRequest -> QueryRequest
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c QueryRequest)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c QueryRequest)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c QueryRequest)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c QueryRequest)
dataTypeOf :: QueryRequest -> DataType
$cdataTypeOf :: QueryRequest -> DataType
toConstr :: QueryRequest -> Constr
$ctoConstr :: QueryRequest -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QueryRequest
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QueryRequest
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QueryRequest -> c QueryRequest
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QueryRequest -> c QueryRequest
$cp1Data :: Typeable QueryRequest
Data, QueryRequest -> QueryRequest -> Bool
(QueryRequest -> QueryRequest -> Bool)
-> (QueryRequest -> QueryRequest -> Bool) -> Eq QueryRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryRequest -> QueryRequest -> Bool
$c/= :: QueryRequest -> QueryRequest -> Bool
== :: QueryRequest -> QueryRequest -> Bool
$c== :: QueryRequest -> QueryRequest -> Bool
Eq, (forall x. QueryRequest -> Rep QueryRequest x)
-> (forall x. Rep QueryRequest x -> QueryRequest)
-> Generic QueryRequest
forall x. Rep QueryRequest x -> QueryRequest
forall x. QueryRequest -> Rep QueryRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep QueryRequest x -> QueryRequest
$cfrom :: forall x. QueryRequest -> Rep QueryRequest x
Generic, Eq QueryRequest
Eq QueryRequest
-> (QueryRequest -> QueryRequest -> Ordering)
-> (QueryRequest -> QueryRequest -> Bool)
-> (QueryRequest -> QueryRequest -> Bool)
-> (QueryRequest -> QueryRequest -> Bool)
-> (QueryRequest -> QueryRequest -> Bool)
-> (QueryRequest -> QueryRequest -> QueryRequest)
-> (QueryRequest -> QueryRequest -> QueryRequest)
-> Ord QueryRequest
QueryRequest -> QueryRequest -> Bool
QueryRequest -> QueryRequest -> Ordering
QueryRequest -> QueryRequest -> QueryRequest
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: QueryRequest -> QueryRequest -> QueryRequest
$cmin :: QueryRequest -> QueryRequest -> QueryRequest
max :: QueryRequest -> QueryRequest -> QueryRequest
$cmax :: QueryRequest -> QueryRequest -> QueryRequest
>= :: QueryRequest -> QueryRequest -> Bool
$c>= :: QueryRequest -> QueryRequest -> Bool
> :: QueryRequest -> QueryRequest -> Bool
$c> :: QueryRequest -> QueryRequest -> Bool
<= :: QueryRequest -> QueryRequest -> Bool
$c<= :: QueryRequest -> QueryRequest -> Bool
< :: QueryRequest -> QueryRequest -> Bool
$c< :: QueryRequest -> QueryRequest -> Bool
compare :: QueryRequest -> QueryRequest -> Ordering
$ccompare :: QueryRequest -> QueryRequest -> Ordering
$cp1Ord :: Eq QueryRequest
Ord, Int -> QueryRequest -> ShowS
[QueryRequest] -> ShowS
QueryRequest -> String
(Int -> QueryRequest -> ShowS)
-> (QueryRequest -> String)
-> ([QueryRequest] -> ShowS)
-> Show QueryRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryRequest] -> ShowS
$cshowList :: [QueryRequest] -> ShowS
show :: QueryRequest -> String
$cshow :: QueryRequest -> String
showsPrec :: Int -> QueryRequest -> ShowS
$cshowsPrec :: Int -> QueryRequest -> ShowS
Show)
instance ToJSON QueryRequest where
toJSON :: QueryRequest -> Value
toJSON = Options -> QueryRequest -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
J.genericToJSON Options
J.defaultOptions
instance Witch.From QueryRequest API.QueryRequest where
from :: QueryRequest -> QueryRequest
from QueryRequest {Name
TableRelationships
Query
_qrQuery :: Query
_qrTableRelationships :: TableRelationships
_qrTable :: Name
_qrQuery :: QueryRequest -> Query
_qrTableRelationships :: QueryRequest -> TableRelationships
_qrTable :: QueryRequest -> Name
..} =
QueryRequest :: TableName -> [TableRelationships] -> Query -> QueryRequest
API.QueryRequest
{ _qrTable :: TableName
_qrTable = Name -> TableName
forall source target. From source target => source -> target
Witch.from Name
_qrTable,
_qrTableRelationships :: [TableRelationships]
_qrTableRelationships =
( \(Name
sourceTableName, HashMap RelationshipName Relationship
relationships) ->
TableRelationships :: TableName
-> HashMap RelationshipName Relationship -> TableRelationships
API.TableRelationships
{ _trSourceTable :: TableName
_trSourceTable = Name -> TableName
forall source target. From source target => source -> target
Witch.from Name
sourceTableName,
_trRelationships :: HashMap RelationshipName Relationship
_trRelationships = (RelationshipName -> RelationshipName)
-> HashMap RelationshipName Relationship
-> HashMap RelationshipName Relationship
forall k2 k1 v.
(Eq k2, Hashable k2) =>
(k1 -> k2) -> HashMap k1 v -> HashMap k2 v
HashMap.mapKeys RelationshipName -> RelationshipName
forall source target. From source target => source -> target
Witch.from (HashMap RelationshipName Relationship
-> HashMap RelationshipName Relationship)
-> HashMap RelationshipName Relationship
-> HashMap RelationshipName Relationship
forall a b. (a -> b) -> a -> b
$ Relationship -> Relationship
forall source target. From source target => source -> target
Witch.from (Relationship -> Relationship)
-> HashMap RelationshipName Relationship
-> HashMap RelationshipName Relationship
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HashMap RelationshipName Relationship
relationships
}
)
((Name, HashMap RelationshipName Relationship)
-> TableRelationships)
-> [(Name, HashMap RelationshipName Relationship)]
-> [TableRelationships]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HashMap Name (HashMap RelationshipName Relationship)
-> [(Name, HashMap RelationshipName Relationship)]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList (TableRelationships
-> HashMap Name (HashMap RelationshipName Relationship)
IR.R.unTableRelationships TableRelationships
_qrTableRelationships),
_qrQuery :: Query
_qrQuery = Query -> Query
forall source target. From source target => source -> target
Witch.from Query
_qrQuery
}
data Query = Query
{
Query -> HashMap FieldName Field
_qFields :: HashMap FieldName Field,
Query -> HashMap FieldName Aggregate
_qAggregates :: HashMap FieldName IR.A.Aggregate,
Query -> Maybe Int
_qLimit :: Maybe Int,
Query -> Maybe Int
_qOffset :: Maybe Int,
Query -> Maybe Expression
_qWhere :: Maybe IR.E.Expression,
Query -> Maybe OrderBy
_qOrderBy :: Maybe IR.O.OrderBy
}
deriving stock (Typeable Query
DataType
Constr
Typeable Query
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Query -> c Query)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Query)
-> (Query -> Constr)
-> (Query -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Query))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Query))
-> ((forall b. Data b => b -> b) -> Query -> Query)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r)
-> (forall u. (forall d. Data d => d -> u) -> Query -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Query -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Query -> m Query)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Query -> m Query)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Query -> m Query)
-> Data Query
Query -> DataType
Query -> Constr
(forall b. Data b => b -> b) -> Query -> Query
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Query -> c Query
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Query
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Query -> u
forall u. (forall d. Data d => d -> u) -> Query -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Query -> m Query
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Query -> m Query
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Query
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Query -> c Query
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Query)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Query)
$cQuery :: Constr
$tQuery :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Query -> m Query
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Query -> m Query
gmapMp :: (forall d. Data d => d -> m d) -> Query -> m Query
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Query -> m Query
gmapM :: (forall d. Data d => d -> m d) -> Query -> m Query
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Query -> m Query
gmapQi :: Int -> (forall d. Data d => d -> u) -> Query -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Query -> u
gmapQ :: (forall d. Data d => d -> u) -> Query -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Query -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r
gmapT :: (forall b. Data b => b -> b) -> Query -> Query
$cgmapT :: (forall b. Data b => b -> b) -> Query -> Query
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Query)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Query)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Query)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Query)
dataTypeOf :: Query -> DataType
$cdataTypeOf :: Query -> DataType
toConstr :: Query -> Constr
$ctoConstr :: Query -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Query
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Query
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Query -> c Query
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Query -> c Query
$cp1Data :: Typeable Query
Data, Query -> Query -> Bool
(Query -> Query -> Bool) -> (Query -> Query -> Bool) -> Eq Query
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Query -> Query -> Bool
$c/= :: Query -> Query -> Bool
== :: Query -> Query -> Bool
$c== :: Query -> Query -> Bool
Eq, (forall x. Query -> Rep Query x)
-> (forall x. Rep Query x -> Query) -> Generic Query
forall x. Rep Query x -> Query
forall x. Query -> Rep Query x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Query x -> Query
$cfrom :: forall x. Query -> Rep Query x
Generic, Eq Query
Eq Query
-> (Query -> Query -> Ordering)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Query)
-> (Query -> Query -> Query)
-> Ord Query
Query -> Query -> Bool
Query -> Query -> Ordering
Query -> Query -> Query
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Query -> Query -> Query
$cmin :: Query -> Query -> Query
max :: Query -> Query -> Query
$cmax :: Query -> Query -> Query
>= :: Query -> Query -> Bool
$c>= :: Query -> Query -> Bool
> :: Query -> Query -> Bool
$c> :: Query -> Query -> Bool
<= :: Query -> Query -> Bool
$c<= :: Query -> Query -> Bool
< :: Query -> Query -> Bool
$c< :: Query -> Query -> Bool
compare :: Query -> Query -> Ordering
$ccompare :: Query -> Query -> Ordering
$cp1Ord :: Eq Query
Ord, Int -> Query -> ShowS
[Query] -> ShowS
Query -> String
(Int -> Query -> ShowS)
-> (Query -> String) -> ([Query] -> ShowS) -> Show Query
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Query] -> ShowS
$cshowList :: [Query] -> ShowS
show :: Query -> String
$cshow :: Query -> String
showsPrec :: Int -> Query -> ShowS
$cshowsPrec :: Int -> Query -> ShowS
Show)
instance ToJSON Query where
toJSON :: Query -> Value
toJSON = Options -> Query -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
J.genericToJSON Options
J.defaultOptions
instance Witch.From Query API.Query where
from :: Query -> Query
from Query {Maybe Int
Maybe Expression
Maybe OrderBy
HashMap FieldName Aggregate
HashMap FieldName Field
_qOrderBy :: Maybe OrderBy
_qWhere :: Maybe Expression
_qOffset :: Maybe Int
_qLimit :: Maybe Int
_qAggregates :: HashMap FieldName Aggregate
_qFields :: HashMap FieldName Field
_qOrderBy :: Query -> Maybe OrderBy
_qWhere :: Query -> Maybe Expression
_qOffset :: Query -> Maybe Int
_qLimit :: Query -> Maybe Int
_qAggregates :: Query -> HashMap FieldName Aggregate
_qFields :: Query -> HashMap FieldName Field
..} =
Query :: Maybe (KeyMap Field)
-> Maybe (KeyMap Aggregate)
-> Maybe Int
-> Maybe Int
-> Maybe Expression
-> Maybe OrderBy
-> Query
API.Query
{ _qFields :: Maybe (KeyMap Field)
_qFields = KeyMap Field -> Maybe (KeyMap Field)
forall m. (Monoid m, Eq m) => m -> Maybe m
memptyToNothing (KeyMap Field -> Maybe (KeyMap Field))
-> ([(Key, Field)] -> KeyMap Field)
-> [(Key, Field)]
-> Maybe (KeyMap Field)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Key, Field)] -> KeyMap Field
forall v. [(Key, v)] -> KeyMap v
KeyMap.fromList ([(Key, Field)] -> Maybe (KeyMap Field))
-> [(Key, Field)] -> Maybe (KeyMap Field)
forall a b. (a -> b) -> a -> b
$ ((FieldName -> Key)
-> (Field -> Field) -> (FieldName, Field) -> (Key, Field)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (Text -> Key
Key.fromText (Text -> Key) -> (FieldName -> Text) -> FieldName -> Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldName -> Text
getFieldNameTxt) Field -> Field
forall source target. From source target => source -> target
Witch.from) ((FieldName, Field) -> (Key, Field))
-> [(FieldName, Field)] -> [(Key, Field)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HashMap FieldName Field -> [(FieldName, Field)]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList HashMap FieldName Field
_qFields,
_qAggregates :: Maybe (KeyMap Aggregate)
_qAggregates = KeyMap Aggregate -> Maybe (KeyMap Aggregate)
forall m. (Monoid m, Eq m) => m -> Maybe m
memptyToNothing (KeyMap Aggregate -> Maybe (KeyMap Aggregate))
-> ([(Key, Aggregate)] -> KeyMap Aggregate)
-> [(Key, Aggregate)]
-> Maybe (KeyMap Aggregate)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Key, Aggregate)] -> KeyMap Aggregate
forall v. [(Key, v)] -> KeyMap v
KeyMap.fromList ([(Key, Aggregate)] -> Maybe (KeyMap Aggregate))
-> [(Key, Aggregate)] -> Maybe (KeyMap Aggregate)
forall a b. (a -> b) -> a -> b
$ ((FieldName -> Key)
-> (Aggregate -> Aggregate)
-> (FieldName, Aggregate)
-> (Key, Aggregate)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (Text -> Key
Key.fromText (Text -> Key) -> (FieldName -> Text) -> FieldName -> Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldName -> Text
getFieldNameTxt) Aggregate -> Aggregate
forall source target. From source target => source -> target
Witch.from) ((FieldName, Aggregate) -> (Key, Aggregate))
-> [(FieldName, Aggregate)] -> [(Key, Aggregate)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HashMap FieldName Aggregate -> [(FieldName, Aggregate)]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList HashMap FieldName Aggregate
_qAggregates,
_qLimit :: Maybe Int
_qLimit = Maybe Int
_qLimit,
_qOffset :: Maybe Int
_qOffset = Maybe Int
_qOffset,
_qWhere :: Maybe Expression
_qWhere = (Expression -> Expression) -> Maybe Expression -> Maybe Expression
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Expression -> Expression
forall source target. From source target => source -> target
Witch.from Maybe Expression
_qWhere,
_qOrderBy :: Maybe OrderBy
_qOrderBy = OrderBy -> OrderBy
forall source target. From source target => source -> target
Witch.from (OrderBy -> OrderBy) -> Maybe OrderBy -> Maybe OrderBy
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe OrderBy
_qOrderBy
}
memptyToNothing :: (Monoid m, Eq m) => m -> Maybe m
memptyToNothing :: m -> Maybe m
memptyToNothing m
m = if m
m m -> m -> Bool
forall a. Eq a => a -> a -> Bool
== m
forall a. Monoid a => a
mempty then Maybe m
forall a. Maybe a
Nothing else m -> Maybe m
forall a. a -> Maybe a
Just m
m
data Field
= ColumnField IR.C.Name
| RelField RelationshipField
deriving stock (Typeable Field
DataType
Constr
Typeable Field
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Field -> c Field)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Field)
-> (Field -> Constr)
-> (Field -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Field))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Field))
-> ((forall b. Data b => b -> b) -> Field -> Field)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Field -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Field -> r)
-> (forall u. (forall d. Data d => d -> u) -> Field -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Field -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Field -> m Field)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Field -> m Field)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Field -> m Field)
-> Data Field
Field -> DataType
Field -> Constr
(forall b. Data b => b -> b) -> Field -> Field
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Field -> c Field
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Field
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Field -> u
forall u. (forall d. Data d => d -> u) -> Field -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Field -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Field -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Field -> m Field
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Field -> m Field
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Field
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Field -> c Field
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Field)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Field)
$cRelField :: Constr
$cColumnField :: Constr
$tField :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Field -> m Field
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Field -> m Field
gmapMp :: (forall d. Data d => d -> m d) -> Field -> m Field
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Field -> m Field
gmapM :: (forall d. Data d => d -> m d) -> Field -> m Field
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Field -> m Field
gmapQi :: Int -> (forall d. Data d => d -> u) -> Field -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Field -> u
gmapQ :: (forall d. Data d => d -> u) -> Field -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Field -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Field -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Field -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Field -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Field -> r
gmapT :: (forall b. Data b => b -> b) -> Field -> Field
$cgmapT :: (forall b. Data b => b -> b) -> Field -> Field
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Field)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Field)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Field)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Field)
dataTypeOf :: Field -> DataType
$cdataTypeOf :: Field -> DataType
toConstr :: Field -> Constr
$ctoConstr :: Field -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Field
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Field
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Field -> c Field
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Field -> c Field
$cp1Data :: Typeable Field
Data, Field -> Field -> Bool
(Field -> Field -> Bool) -> (Field -> Field -> Bool) -> Eq Field
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Field -> Field -> Bool
$c/= :: Field -> Field -> Bool
== :: Field -> Field -> Bool
$c== :: Field -> Field -> Bool
Eq, (forall x. Field -> Rep Field x)
-> (forall x. Rep Field x -> Field) -> Generic Field
forall x. Rep Field x -> Field
forall x. Field -> Rep Field x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Field x -> Field
$cfrom :: forall x. Field -> Rep Field x
Generic, Eq Field
Eq Field
-> (Field -> Field -> Ordering)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Field)
-> (Field -> Field -> Field)
-> Ord Field
Field -> Field -> Bool
Field -> Field -> Ordering
Field -> Field -> Field
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Field -> Field -> Field
$cmin :: Field -> Field -> Field
max :: Field -> Field -> Field
$cmax :: Field -> Field -> Field
>= :: Field -> Field -> Bool
$c>= :: Field -> Field -> Bool
> :: Field -> Field -> Bool
$c> :: Field -> Field -> Bool
<= :: Field -> Field -> Bool
$c<= :: Field -> Field -> Bool
< :: Field -> Field -> Bool
$c< :: Field -> Field -> Bool
compare :: Field -> Field -> Ordering
$ccompare :: Field -> Field -> Ordering
$cp1Ord :: Eq Field
Ord, Int -> Field -> ShowS
[Field] -> ShowS
Field -> String
(Int -> Field -> ShowS)
-> (Field -> String) -> ([Field] -> ShowS) -> Show Field
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Field] -> ShowS
$cshowList :: [Field] -> ShowS
show :: Field -> String
$cshow :: Field -> String
showsPrec :: Int -> Field -> ShowS
$cshowsPrec :: Int -> Field -> ShowS
Show)
instance ToJSON Field where
toJSON :: Field -> Value
toJSON = Options -> Field -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
J.genericToJSON Options
J.defaultOptions
instance Witch.From Field API.Field where
from :: Field -> Field
from (ColumnField Name
name) = ColumnName -> Field
API.ColumnField (ColumnName -> Field) -> ColumnName -> Field
forall a b. (a -> b) -> a -> b
$ Name -> ColumnName
forall source target. From source target => source -> target
Witch.from Name
name
from (RelField RelationshipField
relationshipField) = RelationshipField -> Field
API.RelField (RelationshipField -> Field) -> RelationshipField -> Field
forall a b. (a -> b) -> a -> b
$ RelationshipField -> RelationshipField
forall source target. From source target => source -> target
Witch.from RelationshipField
relationshipField
data RelationshipField = RelationshipField
{ RelationshipField -> RelationshipName
_rfRelationship :: IR.R.RelationshipName,
RelationshipField -> Query
_rfQuery :: Query
}
deriving stock (RelationshipField -> RelationshipField -> Bool
(RelationshipField -> RelationshipField -> Bool)
-> (RelationshipField -> RelationshipField -> Bool)
-> Eq RelationshipField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelationshipField -> RelationshipField -> Bool
$c/= :: RelationshipField -> RelationshipField -> Bool
== :: RelationshipField -> RelationshipField -> Bool
$c== :: RelationshipField -> RelationshipField -> Bool
Eq, Eq RelationshipField
Eq RelationshipField
-> (RelationshipField -> RelationshipField -> Ordering)
-> (RelationshipField -> RelationshipField -> Bool)
-> (RelationshipField -> RelationshipField -> Bool)
-> (RelationshipField -> RelationshipField -> Bool)
-> (RelationshipField -> RelationshipField -> Bool)
-> (RelationshipField -> RelationshipField -> RelationshipField)
-> (RelationshipField -> RelationshipField -> RelationshipField)
-> Ord RelationshipField
RelationshipField -> RelationshipField -> Bool
RelationshipField -> RelationshipField -> Ordering
RelationshipField -> RelationshipField -> RelationshipField
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RelationshipField -> RelationshipField -> RelationshipField
$cmin :: RelationshipField -> RelationshipField -> RelationshipField
max :: RelationshipField -> RelationshipField -> RelationshipField
$cmax :: RelationshipField -> RelationshipField -> RelationshipField
>= :: RelationshipField -> RelationshipField -> Bool
$c>= :: RelationshipField -> RelationshipField -> Bool
> :: RelationshipField -> RelationshipField -> Bool
$c> :: RelationshipField -> RelationshipField -> Bool
<= :: RelationshipField -> RelationshipField -> Bool
$c<= :: RelationshipField -> RelationshipField -> Bool
< :: RelationshipField -> RelationshipField -> Bool
$c< :: RelationshipField -> RelationshipField -> Bool
compare :: RelationshipField -> RelationshipField -> Ordering
$ccompare :: RelationshipField -> RelationshipField -> Ordering
$cp1Ord :: Eq RelationshipField
Ord, Int -> RelationshipField -> ShowS
[RelationshipField] -> ShowS
RelationshipField -> String
(Int -> RelationshipField -> ShowS)
-> (RelationshipField -> String)
-> ([RelationshipField] -> ShowS)
-> Show RelationshipField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RelationshipField] -> ShowS
$cshowList :: [RelationshipField] -> ShowS
show :: RelationshipField -> String
$cshow :: RelationshipField -> String
showsPrec :: Int -> RelationshipField -> ShowS
$cshowsPrec :: Int -> RelationshipField -> ShowS
Show, (forall x. RelationshipField -> Rep RelationshipField x)
-> (forall x. Rep RelationshipField x -> RelationshipField)
-> Generic RelationshipField
forall x. Rep RelationshipField x -> RelationshipField
forall x. RelationshipField -> Rep RelationshipField x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RelationshipField x -> RelationshipField
$cfrom :: forall x. RelationshipField -> Rep RelationshipField x
Generic, Typeable RelationshipField
DataType
Constr
Typeable RelationshipField
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> RelationshipField
-> c RelationshipField)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RelationshipField)
-> (RelationshipField -> Constr)
-> (RelationshipField -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RelationshipField))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RelationshipField))
-> ((forall b. Data b => b -> b)
-> RelationshipField -> RelationshipField)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RelationshipField -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RelationshipField -> r)
-> (forall u.
(forall d. Data d => d -> u) -> RelationshipField -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> RelationshipField -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RelationshipField -> m RelationshipField)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RelationshipField -> m RelationshipField)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RelationshipField -> m RelationshipField)
-> Data RelationshipField
RelationshipField -> DataType
RelationshipField -> Constr
(forall b. Data b => b -> b)
-> RelationshipField -> RelationshipField
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RelationshipField -> c RelationshipField
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RelationshipField
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> RelationshipField -> u
forall u. (forall d. Data d => d -> u) -> RelationshipField -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RelationshipField -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RelationshipField -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RelationshipField -> m RelationshipField
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RelationshipField -> m RelationshipField
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RelationshipField
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RelationshipField -> c RelationshipField
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RelationshipField)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RelationshipField)
$cRelationshipField :: Constr
$tRelationshipField :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> RelationshipField -> m RelationshipField
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RelationshipField -> m RelationshipField
gmapMp :: (forall d. Data d => d -> m d)
-> RelationshipField -> m RelationshipField
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RelationshipField -> m RelationshipField
gmapM :: (forall d. Data d => d -> m d)
-> RelationshipField -> m RelationshipField
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RelationshipField -> m RelationshipField
gmapQi :: Int -> (forall d. Data d => d -> u) -> RelationshipField -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> RelationshipField -> u
gmapQ :: (forall d. Data d => d -> u) -> RelationshipField -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RelationshipField -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RelationshipField -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RelationshipField -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RelationshipField -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RelationshipField -> r
gmapT :: (forall b. Data b => b -> b)
-> RelationshipField -> RelationshipField
$cgmapT :: (forall b. Data b => b -> b)
-> RelationshipField -> RelationshipField
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RelationshipField)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RelationshipField)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c RelationshipField)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RelationshipField)
dataTypeOf :: RelationshipField -> DataType
$cdataTypeOf :: RelationshipField -> DataType
toConstr :: RelationshipField -> Constr
$ctoConstr :: RelationshipField -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RelationshipField
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RelationshipField
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RelationshipField -> c RelationshipField
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RelationshipField -> c RelationshipField
$cp1Data :: Typeable RelationshipField
Data)
instance ToJSON RelationshipField where
toJSON :: RelationshipField -> Value
toJSON = Options -> RelationshipField -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
J.genericToJSON Options
J.defaultOptions
instance Witch.From RelationshipField API.RelationshipField where
from :: RelationshipField -> RelationshipField
from RelationshipField {RelationshipName
Query
_rfQuery :: Query
_rfRelationship :: RelationshipName
_rfQuery :: RelationshipField -> Query
_rfRelationship :: RelationshipField -> RelationshipName
..} =
RelationshipField :: RelationshipName -> Query -> RelationshipField
API.RelationshipField
{ _rfRelationship :: RelationshipName
_rfRelationship = RelationshipName -> RelationshipName
forall source target. From source target => source -> target
Witch.from RelationshipName
_rfRelationship,
_rfQuery :: Query
_rfQuery = Query -> Query
forall source target. From source target => source -> target
Witch.from Query
_rfQuery
}