{-# LANGUAGE TemplateHaskell #-}
module Hasura.RQL.IR.RemoteSchema
(
SelectionSet (..),
DeduplicatedSelectionSet (..),
dssCommonFields,
dssMemberSelectionSets,
ObjectSelectionSet,
mkInterfaceSelectionSet,
mkUnionSelectionSet,
Field (..),
_FieldGraphQL,
_FieldRemote,
GraphQLField (..),
fAlias,
fName,
fArguments,
fDirectives,
fSelectionSet,
mkGraphQLField,
RemoteSchemaRootField (..),
SchemaRemoteRelationshipSelect (..),
RemoteFieldArgument (..),
RemoteSchemaSelect (..),
convertSelectionSet,
convertGraphQLField,
)
where
import Control.Lens.TH (makeLenses, makePrisms)
import Data.HashMap.Strict qualified as HashMap
import Data.HashMap.Strict.InsOrd.Extended qualified as InsOrdHashMap
import Data.HashSet qualified as Set
import Data.List.Extended (longestCommonPrefix)
import Hasura.GraphQL.Parser.Name as GName
import Hasura.GraphQL.Parser.Variable (InputValue)
import Hasura.Prelude
import Hasura.RQL.Types.Common (FieldName)
import Hasura.RQL.Types.ResultCustomization
import Hasura.RQL.Types.ResultCustomization qualified as RQL
import Hasura.RemoteSchema.SchemaCache.Types
import Language.GraphQL.Draft.Syntax qualified as G
data SelectionSet r var
= SelectionSetObject (ObjectSelectionSet r var)
| SelectionSetUnion (DeduplicatedSelectionSet r var)
| SelectionSetInterface (DeduplicatedSelectionSet r var)
| SelectionSetNone
deriving (Int -> SelectionSet r var -> ShowS
[SelectionSet r var] -> ShowS
SelectionSet r var -> String
(Int -> SelectionSet r var -> ShowS)
-> (SelectionSet r var -> String)
-> ([SelectionSet r var] -> ShowS)
-> Show (SelectionSet r var)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall r var.
(Show var, Show r) =>
Int -> SelectionSet r var -> ShowS
forall r var. (Show var, Show r) => [SelectionSet r var] -> ShowS
forall r var. (Show var, Show r) => SelectionSet r var -> String
$cshowsPrec :: forall r var.
(Show var, Show r) =>
Int -> SelectionSet r var -> ShowS
showsPrec :: Int -> SelectionSet r var -> ShowS
$cshow :: forall r var. (Show var, Show r) => SelectionSet r var -> String
show :: SelectionSet r var -> String
$cshowList :: forall r var. (Show var, Show r) => [SelectionSet r var] -> ShowS
showList :: [SelectionSet r var] -> ShowS
Show, SelectionSet r var -> SelectionSet r var -> Bool
(SelectionSet r var -> SelectionSet r var -> Bool)
-> (SelectionSet r var -> SelectionSet r var -> Bool)
-> Eq (SelectionSet r var)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall r var.
(Eq var, Eq r) =>
SelectionSet r var -> SelectionSet r var -> Bool
$c== :: forall r var.
(Eq var, Eq r) =>
SelectionSet r var -> SelectionSet r var -> Bool
== :: SelectionSet r var -> SelectionSet r var -> Bool
$c/= :: forall r var.
(Eq var, Eq r) =>
SelectionSet r var -> SelectionSet r var -> Bool
/= :: SelectionSet r var -> SelectionSet r var -> Bool
Eq, (forall a b. (a -> b) -> SelectionSet r a -> SelectionSet r b)
-> (forall a b. a -> SelectionSet r b -> SelectionSet r a)
-> Functor (SelectionSet r)
forall a b. a -> SelectionSet r b -> SelectionSet r a
forall a b. (a -> b) -> SelectionSet r a -> SelectionSet r b
forall r a b. a -> SelectionSet r b -> SelectionSet r a
forall r a b. (a -> b) -> SelectionSet r a -> SelectionSet r b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall r a b. (a -> b) -> SelectionSet r a -> SelectionSet r b
fmap :: forall a b. (a -> b) -> SelectionSet r a -> SelectionSet r b
$c<$ :: forall r a b. a -> SelectionSet r b -> SelectionSet r a
<$ :: forall a b. a -> SelectionSet r b -> SelectionSet r a
Functor, (forall m. Monoid m => SelectionSet r m -> m)
-> (forall m a. Monoid m => (a -> m) -> SelectionSet r a -> m)
-> (forall m a. Monoid m => (a -> m) -> SelectionSet r a -> m)
-> (forall a b. (a -> b -> b) -> b -> SelectionSet r a -> b)
-> (forall a b. (a -> b -> b) -> b -> SelectionSet r a -> b)
-> (forall b a. (b -> a -> b) -> b -> SelectionSet r a -> b)
-> (forall b a. (b -> a -> b) -> b -> SelectionSet r a -> b)
-> (forall a. (a -> a -> a) -> SelectionSet r a -> a)
-> (forall a. (a -> a -> a) -> SelectionSet r a -> a)
-> (forall a. SelectionSet r a -> [a])
-> (forall a. SelectionSet r a -> Bool)
-> (forall a. SelectionSet r a -> Int)
-> (forall a. Eq a => a -> SelectionSet r a -> Bool)
-> (forall a. Ord a => SelectionSet r a -> a)
-> (forall a. Ord a => SelectionSet r a -> a)
-> (forall a. Num a => SelectionSet r a -> a)
-> (forall a. Num a => SelectionSet r a -> a)
-> Foldable (SelectionSet r)
forall a. Eq a => a -> SelectionSet r a -> Bool
forall a. Num a => SelectionSet r a -> a
forall a. Ord a => SelectionSet r a -> a
forall m. Monoid m => SelectionSet r m -> m
forall a. SelectionSet r a -> Bool
forall a. SelectionSet r a -> Int
forall a. SelectionSet r a -> [a]
forall a. (a -> a -> a) -> SelectionSet r a -> a
forall r a. Eq a => a -> SelectionSet r a -> Bool
forall r a. Num a => SelectionSet r a -> a
forall r a. Ord a => SelectionSet r a -> a
forall m a. Monoid m => (a -> m) -> SelectionSet r a -> m
forall r m. Monoid m => SelectionSet r m -> m
forall r a. SelectionSet r a -> Bool
forall r a. SelectionSet r a -> Int
forall r a. SelectionSet r a -> [a]
forall b a. (b -> a -> b) -> b -> SelectionSet r a -> b
forall a b. (a -> b -> b) -> b -> SelectionSet r a -> b
forall r a. (a -> a -> a) -> SelectionSet r a -> a
forall r m a. Monoid m => (a -> m) -> SelectionSet r a -> m
forall r b a. (b -> a -> b) -> b -> SelectionSet r a -> b
forall r a b. (a -> b -> b) -> b -> SelectionSet r 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 r m. Monoid m => SelectionSet r m -> m
fold :: forall m. Monoid m => SelectionSet r m -> m
$cfoldMap :: forall r m a. Monoid m => (a -> m) -> SelectionSet r a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> SelectionSet r a -> m
$cfoldMap' :: forall r m a. Monoid m => (a -> m) -> SelectionSet r a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> SelectionSet r a -> m
$cfoldr :: forall r a b. (a -> b -> b) -> b -> SelectionSet r a -> b
foldr :: forall a b. (a -> b -> b) -> b -> SelectionSet r a -> b
$cfoldr' :: forall r a b. (a -> b -> b) -> b -> SelectionSet r a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> SelectionSet r a -> b
$cfoldl :: forall r b a. (b -> a -> b) -> b -> SelectionSet r a -> b
foldl :: forall b a. (b -> a -> b) -> b -> SelectionSet r a -> b
$cfoldl' :: forall r b a. (b -> a -> b) -> b -> SelectionSet r a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> SelectionSet r a -> b
$cfoldr1 :: forall r a. (a -> a -> a) -> SelectionSet r a -> a
foldr1 :: forall a. (a -> a -> a) -> SelectionSet r a -> a
$cfoldl1 :: forall r a. (a -> a -> a) -> SelectionSet r a -> a
foldl1 :: forall a. (a -> a -> a) -> SelectionSet r a -> a
$ctoList :: forall r a. SelectionSet r a -> [a]
toList :: forall a. SelectionSet r a -> [a]
$cnull :: forall r a. SelectionSet r a -> Bool
null :: forall a. SelectionSet r a -> Bool
$clength :: forall r a. SelectionSet r a -> Int
length :: forall a. SelectionSet r a -> Int
$celem :: forall r a. Eq a => a -> SelectionSet r a -> Bool
elem :: forall a. Eq a => a -> SelectionSet r a -> Bool
$cmaximum :: forall r a. Ord a => SelectionSet r a -> a
maximum :: forall a. Ord a => SelectionSet r a -> a
$cminimum :: forall r a. Ord a => SelectionSet r a -> a
minimum :: forall a. Ord a => SelectionSet r a -> a
$csum :: forall r a. Num a => SelectionSet r a -> a
sum :: forall a. Num a => SelectionSet r a -> a
$cproduct :: forall r a. Num a => SelectionSet r a -> a
product :: forall a. Num a => SelectionSet r a -> a
Foldable, Functor (SelectionSet r)
Foldable (SelectionSet r)
Functor (SelectionSet r)
-> Foldable (SelectionSet r)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SelectionSet r a -> f (SelectionSet r b))
-> (forall (f :: * -> *) a.
Applicative f =>
SelectionSet r (f a) -> f (SelectionSet r a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SelectionSet r a -> m (SelectionSet r b))
-> (forall (m :: * -> *) a.
Monad m =>
SelectionSet r (m a) -> m (SelectionSet r a))
-> Traversable (SelectionSet r)
forall r. Functor (SelectionSet r)
forall r. Foldable (SelectionSet r)
forall r (m :: * -> *) a.
Monad m =>
SelectionSet r (m a) -> m (SelectionSet r a)
forall r (f :: * -> *) a.
Applicative f =>
SelectionSet r (f a) -> f (SelectionSet r a)
forall r (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SelectionSet r a -> m (SelectionSet r b)
forall r (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SelectionSet r a -> f (SelectionSet r 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 =>
SelectionSet r (m a) -> m (SelectionSet r a)
forall (f :: * -> *) a.
Applicative f =>
SelectionSet r (f a) -> f (SelectionSet r a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SelectionSet r a -> m (SelectionSet r b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SelectionSet r a -> f (SelectionSet r b)
$ctraverse :: forall r (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SelectionSet r a -> f (SelectionSet r b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SelectionSet r a -> f (SelectionSet r b)
$csequenceA :: forall r (f :: * -> *) a.
Applicative f =>
SelectionSet r (f a) -> f (SelectionSet r a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
SelectionSet r (f a) -> f (SelectionSet r a)
$cmapM :: forall r (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SelectionSet r a -> m (SelectionSet r b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SelectionSet r a -> m (SelectionSet r b)
$csequence :: forall r (m :: * -> *) a.
Monad m =>
SelectionSet r (m a) -> m (SelectionSet r a)
sequence :: forall (m :: * -> *) a.
Monad m =>
SelectionSet r (m a) -> m (SelectionSet r a)
Traversable)
data DeduplicatedSelectionSet r var = DeduplicatedSelectionSet
{
forall r var. DeduplicatedSelectionSet r var -> HashSet Name
_dssCommonFields :: Set.HashSet G.Name,
forall r var.
DeduplicatedSelectionSet r var
-> HashMap Name (ObjectSelectionSet r var)
_dssMemberSelectionSets :: HashMap.HashMap G.Name (ObjectSelectionSet r var)
}
deriving (Int -> DeduplicatedSelectionSet r var -> ShowS
[DeduplicatedSelectionSet r var] -> ShowS
DeduplicatedSelectionSet r var -> String
(Int -> DeduplicatedSelectionSet r var -> ShowS)
-> (DeduplicatedSelectionSet r var -> String)
-> ([DeduplicatedSelectionSet r var] -> ShowS)
-> Show (DeduplicatedSelectionSet r var)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall r var.
(Show var, Show r) =>
Int -> DeduplicatedSelectionSet r var -> ShowS
forall r var.
(Show var, Show r) =>
[DeduplicatedSelectionSet r var] -> ShowS
forall r var.
(Show var, Show r) =>
DeduplicatedSelectionSet r var -> String
$cshowsPrec :: forall r var.
(Show var, Show r) =>
Int -> DeduplicatedSelectionSet r var -> ShowS
showsPrec :: Int -> DeduplicatedSelectionSet r var -> ShowS
$cshow :: forall r var.
(Show var, Show r) =>
DeduplicatedSelectionSet r var -> String
show :: DeduplicatedSelectionSet r var -> String
$cshowList :: forall r var.
(Show var, Show r) =>
[DeduplicatedSelectionSet r var] -> ShowS
showList :: [DeduplicatedSelectionSet r var] -> ShowS
Show, DeduplicatedSelectionSet r var
-> DeduplicatedSelectionSet r var -> Bool
(DeduplicatedSelectionSet r var
-> DeduplicatedSelectionSet r var -> Bool)
-> (DeduplicatedSelectionSet r var
-> DeduplicatedSelectionSet r var -> Bool)
-> Eq (DeduplicatedSelectionSet r var)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall r var.
(Eq var, Eq r) =>
DeduplicatedSelectionSet r var
-> DeduplicatedSelectionSet r var -> Bool
$c== :: forall r var.
(Eq var, Eq r) =>
DeduplicatedSelectionSet r var
-> DeduplicatedSelectionSet r var -> Bool
== :: DeduplicatedSelectionSet r var
-> DeduplicatedSelectionSet r var -> Bool
$c/= :: forall r var.
(Eq var, Eq r) =>
DeduplicatedSelectionSet r var
-> DeduplicatedSelectionSet r var -> Bool
/= :: DeduplicatedSelectionSet r var
-> DeduplicatedSelectionSet r var -> Bool
Eq, (forall a b.
(a -> b)
-> DeduplicatedSelectionSet r a -> DeduplicatedSelectionSet r b)
-> (forall a b.
a -> DeduplicatedSelectionSet r b -> DeduplicatedSelectionSet r a)
-> Functor (DeduplicatedSelectionSet r)
forall a b.
a -> DeduplicatedSelectionSet r b -> DeduplicatedSelectionSet r a
forall a b.
(a -> b)
-> DeduplicatedSelectionSet r a -> DeduplicatedSelectionSet r b
forall r a b.
a -> DeduplicatedSelectionSet r b -> DeduplicatedSelectionSet r a
forall r a b.
(a -> b)
-> DeduplicatedSelectionSet r a -> DeduplicatedSelectionSet r b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall r a b.
(a -> b)
-> DeduplicatedSelectionSet r a -> DeduplicatedSelectionSet r b
fmap :: forall a b.
(a -> b)
-> DeduplicatedSelectionSet r a -> DeduplicatedSelectionSet r b
$c<$ :: forall r a b.
a -> DeduplicatedSelectionSet r b -> DeduplicatedSelectionSet r a
<$ :: forall a b.
a -> DeduplicatedSelectionSet r b -> DeduplicatedSelectionSet r a
Functor, (forall m. Monoid m => DeduplicatedSelectionSet r m -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> DeduplicatedSelectionSet r a -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> DeduplicatedSelectionSet r a -> m)
-> (forall a b.
(a -> b -> b) -> b -> DeduplicatedSelectionSet r a -> b)
-> (forall a b.
(a -> b -> b) -> b -> DeduplicatedSelectionSet r a -> b)
-> (forall b a.
(b -> a -> b) -> b -> DeduplicatedSelectionSet r a -> b)
-> (forall b a.
(b -> a -> b) -> b -> DeduplicatedSelectionSet r a -> b)
-> (forall a. (a -> a -> a) -> DeduplicatedSelectionSet r a -> a)
-> (forall a. (a -> a -> a) -> DeduplicatedSelectionSet r a -> a)
-> (forall a. DeduplicatedSelectionSet r a -> [a])
-> (forall a. DeduplicatedSelectionSet r a -> Bool)
-> (forall a. DeduplicatedSelectionSet r a -> Int)
-> (forall a. Eq a => a -> DeduplicatedSelectionSet r a -> Bool)
-> (forall a. Ord a => DeduplicatedSelectionSet r a -> a)
-> (forall a. Ord a => DeduplicatedSelectionSet r a -> a)
-> (forall a. Num a => DeduplicatedSelectionSet r a -> a)
-> (forall a. Num a => DeduplicatedSelectionSet r a -> a)
-> Foldable (DeduplicatedSelectionSet r)
forall a. Eq a => a -> DeduplicatedSelectionSet r a -> Bool
forall a. Num a => DeduplicatedSelectionSet r a -> a
forall a. Ord a => DeduplicatedSelectionSet r a -> a
forall m. Monoid m => DeduplicatedSelectionSet r m -> m
forall a. DeduplicatedSelectionSet r a -> Bool
forall a. DeduplicatedSelectionSet r a -> Int
forall a. DeduplicatedSelectionSet r a -> [a]
forall a. (a -> a -> a) -> DeduplicatedSelectionSet r a -> a
forall r a. Eq a => a -> DeduplicatedSelectionSet r a -> Bool
forall r a. Num a => DeduplicatedSelectionSet r a -> a
forall r a. Ord a => DeduplicatedSelectionSet r a -> a
forall m a.
Monoid m =>
(a -> m) -> DeduplicatedSelectionSet r a -> m
forall r m. Monoid m => DeduplicatedSelectionSet r m -> m
forall r a. DeduplicatedSelectionSet r a -> Bool
forall r a. DeduplicatedSelectionSet r a -> Int
forall r a. DeduplicatedSelectionSet r a -> [a]
forall b a. (b -> a -> b) -> b -> DeduplicatedSelectionSet r a -> b
forall a b. (a -> b -> b) -> b -> DeduplicatedSelectionSet r a -> b
forall r a. (a -> a -> a) -> DeduplicatedSelectionSet r a -> a
forall r m a.
Monoid m =>
(a -> m) -> DeduplicatedSelectionSet r a -> m
forall r b a.
(b -> a -> b) -> b -> DeduplicatedSelectionSet r a -> b
forall r a b.
(a -> b -> b) -> b -> DeduplicatedSelectionSet r 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 r m. Monoid m => DeduplicatedSelectionSet r m -> m
fold :: forall m. Monoid m => DeduplicatedSelectionSet r m -> m
$cfoldMap :: forall r m a.
Monoid m =>
(a -> m) -> DeduplicatedSelectionSet r a -> m
foldMap :: forall m a.
Monoid m =>
(a -> m) -> DeduplicatedSelectionSet r a -> m
$cfoldMap' :: forall r m a.
Monoid m =>
(a -> m) -> DeduplicatedSelectionSet r a -> m
foldMap' :: forall m a.
Monoid m =>
(a -> m) -> DeduplicatedSelectionSet r a -> m
$cfoldr :: forall r a b.
(a -> b -> b) -> b -> DeduplicatedSelectionSet r a -> b
foldr :: forall a b. (a -> b -> b) -> b -> DeduplicatedSelectionSet r a -> b
$cfoldr' :: forall r a b.
(a -> b -> b) -> b -> DeduplicatedSelectionSet r a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> DeduplicatedSelectionSet r a -> b
$cfoldl :: forall r b a.
(b -> a -> b) -> b -> DeduplicatedSelectionSet r a -> b
foldl :: forall b a. (b -> a -> b) -> b -> DeduplicatedSelectionSet r a -> b
$cfoldl' :: forall r b a.
(b -> a -> b) -> b -> DeduplicatedSelectionSet r a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> DeduplicatedSelectionSet r a -> b
$cfoldr1 :: forall r a. (a -> a -> a) -> DeduplicatedSelectionSet r a -> a
foldr1 :: forall a. (a -> a -> a) -> DeduplicatedSelectionSet r a -> a
$cfoldl1 :: forall r a. (a -> a -> a) -> DeduplicatedSelectionSet r a -> a
foldl1 :: forall a. (a -> a -> a) -> DeduplicatedSelectionSet r a -> a
$ctoList :: forall r a. DeduplicatedSelectionSet r a -> [a]
toList :: forall a. DeduplicatedSelectionSet r a -> [a]
$cnull :: forall r a. DeduplicatedSelectionSet r a -> Bool
null :: forall a. DeduplicatedSelectionSet r a -> Bool
$clength :: forall r a. DeduplicatedSelectionSet r a -> Int
length :: forall a. DeduplicatedSelectionSet r a -> Int
$celem :: forall r a. Eq a => a -> DeduplicatedSelectionSet r a -> Bool
elem :: forall a. Eq a => a -> DeduplicatedSelectionSet r a -> Bool
$cmaximum :: forall r a. Ord a => DeduplicatedSelectionSet r a -> a
maximum :: forall a. Ord a => DeduplicatedSelectionSet r a -> a
$cminimum :: forall r a. Ord a => DeduplicatedSelectionSet r a -> a
minimum :: forall a. Ord a => DeduplicatedSelectionSet r a -> a
$csum :: forall r a. Num a => DeduplicatedSelectionSet r a -> a
sum :: forall a. Num a => DeduplicatedSelectionSet r a -> a
$cproduct :: forall r a. Num a => DeduplicatedSelectionSet r a -> a
product :: forall a. Num a => DeduplicatedSelectionSet r a -> a
Foldable, Functor (DeduplicatedSelectionSet r)
Foldable (DeduplicatedSelectionSet r)
Functor (DeduplicatedSelectionSet r)
-> Foldable (DeduplicatedSelectionSet r)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> DeduplicatedSelectionSet r a
-> f (DeduplicatedSelectionSet r b))
-> (forall (f :: * -> *) a.
Applicative f =>
DeduplicatedSelectionSet r (f a)
-> f (DeduplicatedSelectionSet r a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> DeduplicatedSelectionSet r a
-> m (DeduplicatedSelectionSet r b))
-> (forall (m :: * -> *) a.
Monad m =>
DeduplicatedSelectionSet r (m a)
-> m (DeduplicatedSelectionSet r a))
-> Traversable (DeduplicatedSelectionSet r)
forall r. Functor (DeduplicatedSelectionSet r)
forall r. Foldable (DeduplicatedSelectionSet r)
forall r (m :: * -> *) a.
Monad m =>
DeduplicatedSelectionSet r (m a)
-> m (DeduplicatedSelectionSet r a)
forall r (f :: * -> *) a.
Applicative f =>
DeduplicatedSelectionSet r (f a)
-> f (DeduplicatedSelectionSet r a)
forall r (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> DeduplicatedSelectionSet r a -> m (DeduplicatedSelectionSet r b)
forall r (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> DeduplicatedSelectionSet r a -> f (DeduplicatedSelectionSet r 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 =>
DeduplicatedSelectionSet r (m a)
-> m (DeduplicatedSelectionSet r a)
forall (f :: * -> *) a.
Applicative f =>
DeduplicatedSelectionSet r (f a)
-> f (DeduplicatedSelectionSet r a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> DeduplicatedSelectionSet r a -> m (DeduplicatedSelectionSet r b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> DeduplicatedSelectionSet r a -> f (DeduplicatedSelectionSet r b)
$ctraverse :: forall r (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> DeduplicatedSelectionSet r a -> f (DeduplicatedSelectionSet r b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> DeduplicatedSelectionSet r a -> f (DeduplicatedSelectionSet r b)
$csequenceA :: forall r (f :: * -> *) a.
Applicative f =>
DeduplicatedSelectionSet r (f a)
-> f (DeduplicatedSelectionSet r a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
DeduplicatedSelectionSet r (f a)
-> f (DeduplicatedSelectionSet r a)
$cmapM :: forall r (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> DeduplicatedSelectionSet r a -> m (DeduplicatedSelectionSet r b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> DeduplicatedSelectionSet r a -> m (DeduplicatedSelectionSet r b)
$csequence :: forall r (m :: * -> *) a.
Monad m =>
DeduplicatedSelectionSet r (m a)
-> m (DeduplicatedSelectionSet r a)
sequence :: forall (m :: * -> *) a.
Monad m =>
DeduplicatedSelectionSet r (m a)
-> m (DeduplicatedSelectionSet r a)
Traversable, (forall x.
DeduplicatedSelectionSet r var
-> Rep (DeduplicatedSelectionSet r var) x)
-> (forall x.
Rep (DeduplicatedSelectionSet r var) x
-> DeduplicatedSelectionSet r var)
-> Generic (DeduplicatedSelectionSet r var)
forall x.
Rep (DeduplicatedSelectionSet r var) x
-> DeduplicatedSelectionSet r var
forall x.
DeduplicatedSelectionSet r var
-> Rep (DeduplicatedSelectionSet r var) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall r var x.
Rep (DeduplicatedSelectionSet r var) x
-> DeduplicatedSelectionSet r var
forall r var x.
DeduplicatedSelectionSet r var
-> Rep (DeduplicatedSelectionSet r var) x
$cfrom :: forall r var x.
DeduplicatedSelectionSet r var
-> Rep (DeduplicatedSelectionSet r var) x
from :: forall x.
DeduplicatedSelectionSet r var
-> Rep (DeduplicatedSelectionSet r var) x
$cto :: forall r var x.
Rep (DeduplicatedSelectionSet r var) x
-> DeduplicatedSelectionSet r var
to :: forall x.
Rep (DeduplicatedSelectionSet r var) x
-> DeduplicatedSelectionSet r var
Generic)
type ObjectSelectionSet r var = InsOrdHashMap.InsOrdHashMap G.Name (Field r var)
mkInterfaceSelectionSet ::
Set.HashSet G.Name ->
[(G.Name, ObjectSelectionSet r var)] ->
DeduplicatedSelectionSet r var
mkInterfaceSelectionSet :: forall r var.
HashSet Name
-> [(Name, ObjectSelectionSet r var)]
-> DeduplicatedSelectionSet r var
mkInterfaceSelectionSet HashSet Name
interfaceFields [(Name, ObjectSelectionSet r var)]
selectionSets =
HashSet Name
-> HashMap Name (ObjectSelectionSet r var)
-> DeduplicatedSelectionSet r var
forall r var.
HashSet Name
-> HashMap Name (ObjectSelectionSet r var)
-> DeduplicatedSelectionSet r var
DeduplicatedSelectionSet
(Name -> HashSet Name -> HashSet Name
forall a. (Eq a, Hashable a) => a -> HashSet a -> HashSet a
Set.insert Name
GName.___typename HashSet Name
interfaceFields)
([(Name, ObjectSelectionSet r var)]
-> HashMap Name (ObjectSelectionSet r var)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList [(Name, ObjectSelectionSet r var)]
selectionSets)
mkUnionSelectionSet ::
[(G.Name, ObjectSelectionSet r var)] ->
DeduplicatedSelectionSet r var
mkUnionSelectionSet :: forall r var.
[(Name, ObjectSelectionSet r var)]
-> DeduplicatedSelectionSet r var
mkUnionSelectionSet [(Name, ObjectSelectionSet r var)]
selectionSets =
HashSet Name
-> HashMap Name (ObjectSelectionSet r var)
-> DeduplicatedSelectionSet r var
forall r var.
HashSet Name
-> HashMap Name (ObjectSelectionSet r var)
-> DeduplicatedSelectionSet r var
DeduplicatedSelectionSet
(Name -> HashSet Name
forall a. Hashable a => a -> HashSet a
Set.singleton Name
GName.___typename)
([(Name, ObjectSelectionSet r var)]
-> HashMap Name (ObjectSelectionSet r var)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList [(Name, ObjectSelectionSet r var)]
selectionSets)
data Field r var
= FieldGraphQL (GraphQLField r var)
| FieldRemote (SchemaRemoteRelationshipSelect r)
deriving (Int -> Field r var -> ShowS
[Field r var] -> ShowS
Field r var -> String
(Int -> Field r var -> ShowS)
-> (Field r var -> String)
-> ([Field r var] -> ShowS)
-> Show (Field r var)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall r var. (Show var, Show r) => Int -> Field r var -> ShowS
forall r var. (Show var, Show r) => [Field r var] -> ShowS
forall r var. (Show var, Show r) => Field r var -> String
$cshowsPrec :: forall r var. (Show var, Show r) => Int -> Field r var -> ShowS
showsPrec :: Int -> Field r var -> ShowS
$cshow :: forall r var. (Show var, Show r) => Field r var -> String
show :: Field r var -> String
$cshowList :: forall r var. (Show var, Show r) => [Field r var] -> ShowS
showList :: [Field r var] -> ShowS
Show, Field r var -> Field r var -> Bool
(Field r var -> Field r var -> Bool)
-> (Field r var -> Field r var -> Bool) -> Eq (Field r var)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall r var. (Eq var, Eq r) => Field r var -> Field r var -> Bool
$c== :: forall r var. (Eq var, Eq r) => Field r var -> Field r var -> Bool
== :: Field r var -> Field r var -> Bool
$c/= :: forall r var. (Eq var, Eq r) => Field r var -> Field r var -> Bool
/= :: Field r var -> Field r var -> Bool
Eq, (forall a b. (a -> b) -> Field r a -> Field r b)
-> (forall a b. a -> Field r b -> Field r a) -> Functor (Field r)
forall a b. a -> Field r b -> Field r a
forall a b. (a -> b) -> Field r a -> Field r b
forall r a b. a -> Field r b -> Field r a
forall r a b. (a -> b) -> Field r a -> Field r b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall r a b. (a -> b) -> Field r a -> Field r b
fmap :: forall a b. (a -> b) -> Field r a -> Field r b
$c<$ :: forall r a b. a -> Field r b -> Field r a
<$ :: forall a b. a -> Field r b -> Field r a
Functor, (forall m. Monoid m => Field r m -> m)
-> (forall m a. Monoid m => (a -> m) -> Field r a -> m)
-> (forall m a. Monoid m => (a -> m) -> Field r a -> m)
-> (forall a b. (a -> b -> b) -> b -> Field r a -> b)
-> (forall a b. (a -> b -> b) -> b -> Field r a -> b)
-> (forall b a. (b -> a -> b) -> b -> Field r a -> b)
-> (forall b a. (b -> a -> b) -> b -> Field r a -> b)
-> (forall a. (a -> a -> a) -> Field r a -> a)
-> (forall a. (a -> a -> a) -> Field r a -> a)
-> (forall a. Field r a -> [a])
-> (forall a. Field r a -> Bool)
-> (forall a. Field r a -> Int)
-> (forall a. Eq a => a -> Field r a -> Bool)
-> (forall a. Ord a => Field r a -> a)
-> (forall a. Ord a => Field r a -> a)
-> (forall a. Num a => Field r a -> a)
-> (forall a. Num a => Field r a -> a)
-> Foldable (Field r)
forall a. Eq a => a -> Field r a -> Bool
forall a. Num a => Field r a -> a
forall a. Ord a => Field r a -> a
forall m. Monoid m => Field r m -> m
forall a. Field r a -> Bool
forall a. Field r a -> Int
forall a. Field r a -> [a]
forall a. (a -> a -> a) -> Field r a -> a
forall r a. Eq a => a -> Field r a -> Bool
forall r a. Num a => Field r a -> a
forall r a. Ord a => Field r a -> a
forall m a. Monoid m => (a -> m) -> Field r a -> m
forall r m. Monoid m => Field r m -> m
forall r a. Field r a -> Bool
forall r a. Field r a -> Int
forall r a. Field r a -> [a]
forall b a. (b -> a -> b) -> b -> Field r a -> b
forall a b. (a -> b -> b) -> b -> Field r a -> b
forall r a. (a -> a -> a) -> Field r a -> a
forall r m a. Monoid m => (a -> m) -> Field r a -> m
forall r b a. (b -> a -> b) -> b -> Field r a -> b
forall r a b. (a -> b -> b) -> b -> Field r 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 r m. Monoid m => Field r m -> m
fold :: forall m. Monoid m => Field r m -> m
$cfoldMap :: forall r m a. Monoid m => (a -> m) -> Field r a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Field r a -> m
$cfoldMap' :: forall r m a. Monoid m => (a -> m) -> Field r a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> Field r a -> m
$cfoldr :: forall r a b. (a -> b -> b) -> b -> Field r a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Field r a -> b
$cfoldr' :: forall r a b. (a -> b -> b) -> b -> Field r a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Field r a -> b
$cfoldl :: forall r b a. (b -> a -> b) -> b -> Field r a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Field r a -> b
$cfoldl' :: forall r b a. (b -> a -> b) -> b -> Field r a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> Field r a -> b
$cfoldr1 :: forall r a. (a -> a -> a) -> Field r a -> a
foldr1 :: forall a. (a -> a -> a) -> Field r a -> a
$cfoldl1 :: forall r a. (a -> a -> a) -> Field r a -> a
foldl1 :: forall a. (a -> a -> a) -> Field r a -> a
$ctoList :: forall r a. Field r a -> [a]
toList :: forall a. Field r a -> [a]
$cnull :: forall r a. Field r a -> Bool
null :: forall a. Field r a -> Bool
$clength :: forall r a. Field r a -> Int
length :: forall a. Field r a -> Int
$celem :: forall r a. Eq a => a -> Field r a -> Bool
elem :: forall a. Eq a => a -> Field r a -> Bool
$cmaximum :: forall r a. Ord a => Field r a -> a
maximum :: forall a. Ord a => Field r a -> a
$cminimum :: forall r a. Ord a => Field r a -> a
minimum :: forall a. Ord a => Field r a -> a
$csum :: forall r a. Num a => Field r a -> a
sum :: forall a. Num a => Field r a -> a
$cproduct :: forall r a. Num a => Field r a -> a
product :: forall a. Num a => Field r a -> a
Foldable, Functor (Field r)
Foldable (Field r)
Functor (Field r)
-> Foldable (Field r)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Field r a -> f (Field r b))
-> (forall (f :: * -> *) a.
Applicative f =>
Field r (f a) -> f (Field r a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Field r a -> m (Field r b))
-> (forall (m :: * -> *) a.
Monad m =>
Field r (m a) -> m (Field r a))
-> Traversable (Field r)
forall r. Functor (Field r)
forall r. Foldable (Field r)
forall r (m :: * -> *) a. Monad m => Field r (m a) -> m (Field r a)
forall r (f :: * -> *) a.
Applicative f =>
Field r (f a) -> f (Field r a)
forall r (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Field r a -> m (Field r b)
forall r (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Field r a -> f (Field r 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 => Field r (m a) -> m (Field r a)
forall (f :: * -> *) a.
Applicative f =>
Field r (f a) -> f (Field r a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Field r a -> m (Field r b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Field r a -> f (Field r b)
$ctraverse :: forall r (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Field r a -> f (Field r b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Field r a -> f (Field r b)
$csequenceA :: forall r (f :: * -> *) a.
Applicative f =>
Field r (f a) -> f (Field r a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Field r (f a) -> f (Field r a)
$cmapM :: forall r (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Field r a -> m (Field r b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Field r a -> m (Field r b)
$csequence :: forall r (m :: * -> *) a. Monad m => Field r (m a) -> m (Field r a)
sequence :: forall (m :: * -> *) a. Monad m => Field r (m a) -> m (Field r a)
Traversable)
data GraphQLField r var = GraphQLField
{ forall r var. GraphQLField r var -> Name
_fAlias :: G.Name,
forall r var. GraphQLField r var -> Name
_fName :: G.Name,
forall r var. GraphQLField r var -> HashMap Name (Value var)
_fArguments :: HashMap G.Name (G.Value var),
forall r var. GraphQLField r var -> [Directive var]
_fDirectives :: [G.Directive var],
forall r var. GraphQLField r var -> SelectionSet r var
_fSelectionSet :: SelectionSet r var
}
deriving (Int -> GraphQLField r var -> ShowS
[GraphQLField r var] -> ShowS
GraphQLField r var -> String
(Int -> GraphQLField r var -> ShowS)
-> (GraphQLField r var -> String)
-> ([GraphQLField r var] -> ShowS)
-> Show (GraphQLField r var)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall r var.
(Show var, Show r) =>
Int -> GraphQLField r var -> ShowS
forall r var. (Show var, Show r) => [GraphQLField r var] -> ShowS
forall r var. (Show var, Show r) => GraphQLField r var -> String
$cshowsPrec :: forall r var.
(Show var, Show r) =>
Int -> GraphQLField r var -> ShowS
showsPrec :: Int -> GraphQLField r var -> ShowS
$cshow :: forall r var. (Show var, Show r) => GraphQLField r var -> String
show :: GraphQLField r var -> String
$cshowList :: forall r var. (Show var, Show r) => [GraphQLField r var] -> ShowS
showList :: [GraphQLField r var] -> ShowS
Show, GraphQLField r var -> GraphQLField r var -> Bool
(GraphQLField r var -> GraphQLField r var -> Bool)
-> (GraphQLField r var -> GraphQLField r var -> Bool)
-> Eq (GraphQLField r var)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall r var.
(Eq var, Eq r) =>
GraphQLField r var -> GraphQLField r var -> Bool
$c== :: forall r var.
(Eq var, Eq r) =>
GraphQLField r var -> GraphQLField r var -> Bool
== :: GraphQLField r var -> GraphQLField r var -> Bool
$c/= :: forall r var.
(Eq var, Eq r) =>
GraphQLField r var -> GraphQLField r var -> Bool
/= :: GraphQLField r var -> GraphQLField r var -> Bool
Eq, (forall a b. (a -> b) -> GraphQLField r a -> GraphQLField r b)
-> (forall a b. a -> GraphQLField r b -> GraphQLField r a)
-> Functor (GraphQLField r)
forall a b. a -> GraphQLField r b -> GraphQLField r a
forall a b. (a -> b) -> GraphQLField r a -> GraphQLField r b
forall r a b. a -> GraphQLField r b -> GraphQLField r a
forall r a b. (a -> b) -> GraphQLField r a -> GraphQLField r b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall r a b. (a -> b) -> GraphQLField r a -> GraphQLField r b
fmap :: forall a b. (a -> b) -> GraphQLField r a -> GraphQLField r b
$c<$ :: forall r a b. a -> GraphQLField r b -> GraphQLField r a
<$ :: forall a b. a -> GraphQLField r b -> GraphQLField r a
Functor, (forall m. Monoid m => GraphQLField r m -> m)
-> (forall m a. Monoid m => (a -> m) -> GraphQLField r a -> m)
-> (forall m a. Monoid m => (a -> m) -> GraphQLField r a -> m)
-> (forall a b. (a -> b -> b) -> b -> GraphQLField r a -> b)
-> (forall a b. (a -> b -> b) -> b -> GraphQLField r a -> b)
-> (forall b a. (b -> a -> b) -> b -> GraphQLField r a -> b)
-> (forall b a. (b -> a -> b) -> b -> GraphQLField r a -> b)
-> (forall a. (a -> a -> a) -> GraphQLField r a -> a)
-> (forall a. (a -> a -> a) -> GraphQLField r a -> a)
-> (forall a. GraphQLField r a -> [a])
-> (forall a. GraphQLField r a -> Bool)
-> (forall a. GraphQLField r a -> Int)
-> (forall a. Eq a => a -> GraphQLField r a -> Bool)
-> (forall a. Ord a => GraphQLField r a -> a)
-> (forall a. Ord a => GraphQLField r a -> a)
-> (forall a. Num a => GraphQLField r a -> a)
-> (forall a. Num a => GraphQLField r a -> a)
-> Foldable (GraphQLField r)
forall a. Eq a => a -> GraphQLField r a -> Bool
forall a. Num a => GraphQLField r a -> a
forall a. Ord a => GraphQLField r a -> a
forall m. Monoid m => GraphQLField r m -> m
forall a. GraphQLField r a -> Bool
forall a. GraphQLField r a -> Int
forall a. GraphQLField r a -> [a]
forall a. (a -> a -> a) -> GraphQLField r a -> a
forall r a. Eq a => a -> GraphQLField r a -> Bool
forall r a. Num a => GraphQLField r a -> a
forall r a. Ord a => GraphQLField r a -> a
forall m a. Monoid m => (a -> m) -> GraphQLField r a -> m
forall r m. Monoid m => GraphQLField r m -> m
forall r a. GraphQLField r a -> Bool
forall r a. GraphQLField r a -> Int
forall r a. GraphQLField r a -> [a]
forall b a. (b -> a -> b) -> b -> GraphQLField r a -> b
forall a b. (a -> b -> b) -> b -> GraphQLField r a -> b
forall r a. (a -> a -> a) -> GraphQLField r a -> a
forall r m a. Monoid m => (a -> m) -> GraphQLField r a -> m
forall r b a. (b -> a -> b) -> b -> GraphQLField r a -> b
forall r a b. (a -> b -> b) -> b -> GraphQLField r 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 r m. Monoid m => GraphQLField r m -> m
fold :: forall m. Monoid m => GraphQLField r m -> m
$cfoldMap :: forall r m a. Monoid m => (a -> m) -> GraphQLField r a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> GraphQLField r a -> m
$cfoldMap' :: forall r m a. Monoid m => (a -> m) -> GraphQLField r a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> GraphQLField r a -> m
$cfoldr :: forall r a b. (a -> b -> b) -> b -> GraphQLField r a -> b
foldr :: forall a b. (a -> b -> b) -> b -> GraphQLField r a -> b
$cfoldr' :: forall r a b. (a -> b -> b) -> b -> GraphQLField r a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> GraphQLField r a -> b
$cfoldl :: forall r b a. (b -> a -> b) -> b -> GraphQLField r a -> b
foldl :: forall b a. (b -> a -> b) -> b -> GraphQLField r a -> b
$cfoldl' :: forall r b a. (b -> a -> b) -> b -> GraphQLField r a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> GraphQLField r a -> b
$cfoldr1 :: forall r a. (a -> a -> a) -> GraphQLField r a -> a
foldr1 :: forall a. (a -> a -> a) -> GraphQLField r a -> a
$cfoldl1 :: forall r a. (a -> a -> a) -> GraphQLField r a -> a
foldl1 :: forall a. (a -> a -> a) -> GraphQLField r a -> a
$ctoList :: forall r a. GraphQLField r a -> [a]
toList :: forall a. GraphQLField r a -> [a]
$cnull :: forall r a. GraphQLField r a -> Bool
null :: forall a. GraphQLField r a -> Bool
$clength :: forall r a. GraphQLField r a -> Int
length :: forall a. GraphQLField r a -> Int
$celem :: forall r a. Eq a => a -> GraphQLField r a -> Bool
elem :: forall a. Eq a => a -> GraphQLField r a -> Bool
$cmaximum :: forall r a. Ord a => GraphQLField r a -> a
maximum :: forall a. Ord a => GraphQLField r a -> a
$cminimum :: forall r a. Ord a => GraphQLField r a -> a
minimum :: forall a. Ord a => GraphQLField r a -> a
$csum :: forall r a. Num a => GraphQLField r a -> a
sum :: forall a. Num a => GraphQLField r a -> a
$cproduct :: forall r a. Num a => GraphQLField r a -> a
product :: forall a. Num a => GraphQLField r a -> a
Foldable, Functor (GraphQLField r)
Foldable (GraphQLField r)
Functor (GraphQLField r)
-> Foldable (GraphQLField r)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GraphQLField r a -> f (GraphQLField r b))
-> (forall (f :: * -> *) a.
Applicative f =>
GraphQLField r (f a) -> f (GraphQLField r a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GraphQLField r a -> m (GraphQLField r b))
-> (forall (m :: * -> *) a.
Monad m =>
GraphQLField r (m a) -> m (GraphQLField r a))
-> Traversable (GraphQLField r)
forall r. Functor (GraphQLField r)
forall r. Foldable (GraphQLField r)
forall r (m :: * -> *) a.
Monad m =>
GraphQLField r (m a) -> m (GraphQLField r a)
forall r (f :: * -> *) a.
Applicative f =>
GraphQLField r (f a) -> f (GraphQLField r a)
forall r (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GraphQLField r a -> m (GraphQLField r b)
forall r (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GraphQLField r a -> f (GraphQLField r 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 =>
GraphQLField r (m a) -> m (GraphQLField r a)
forall (f :: * -> *) a.
Applicative f =>
GraphQLField r (f a) -> f (GraphQLField r a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GraphQLField r a -> m (GraphQLField r b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GraphQLField r a -> f (GraphQLField r b)
$ctraverse :: forall r (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GraphQLField r a -> f (GraphQLField r b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> GraphQLField r a -> f (GraphQLField r b)
$csequenceA :: forall r (f :: * -> *) a.
Applicative f =>
GraphQLField r (f a) -> f (GraphQLField r a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
GraphQLField r (f a) -> f (GraphQLField r a)
$cmapM :: forall r (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GraphQLField r a -> m (GraphQLField r b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> GraphQLField r a -> m (GraphQLField r b)
$csequence :: forall r (m :: * -> *) a.
Monad m =>
GraphQLField r (m a) -> m (GraphQLField r a)
sequence :: forall (m :: * -> *) a.
Monad m =>
GraphQLField r (m a) -> m (GraphQLField r a)
Traversable)
mkGraphQLField ::
Maybe G.Name ->
G.Name ->
HashMap G.Name (G.Value var) ->
[G.Directive var] ->
SelectionSet r var ->
GraphQLField r var
mkGraphQLField :: forall var r.
Maybe Name
-> Name
-> HashMap Name (Value var)
-> [Directive var]
-> SelectionSet r var
-> GraphQLField r var
mkGraphQLField Maybe Name
alias Name
name =
Name
-> Name
-> HashMap Name (Value var)
-> [Directive var]
-> SelectionSet r var
-> GraphQLField r var
forall r var.
Name
-> Name
-> HashMap Name (Value var)
-> [Directive var]
-> SelectionSet r var
-> GraphQLField r var
GraphQLField (Name -> Maybe Name -> Name
forall a. a -> Maybe a -> a
fromMaybe Name
name Maybe Name
alias) Name
name
data RemoteSchemaRootField r var = RemoteSchemaRootField
{ forall r var. RemoteSchemaRootField r var -> RemoteSchemaInfo
_rfRemoteSchemaInfo :: RemoteSchemaInfo,
forall r var. RemoteSchemaRootField r var -> ResultCustomizer
_rfResultCustomizer :: RQL.ResultCustomizer,
forall r var. RemoteSchemaRootField r var -> GraphQLField r var
_rfField :: GraphQLField r var
}
deriving ((forall a b.
(a -> b) -> RemoteSchemaRootField r a -> RemoteSchemaRootField r b)
-> (forall a b.
a -> RemoteSchemaRootField r b -> RemoteSchemaRootField r a)
-> Functor (RemoteSchemaRootField r)
forall a b.
a -> RemoteSchemaRootField r b -> RemoteSchemaRootField r a
forall a b.
(a -> b) -> RemoteSchemaRootField r a -> RemoteSchemaRootField r b
forall r a b.
a -> RemoteSchemaRootField r b -> RemoteSchemaRootField r a
forall r a b.
(a -> b) -> RemoteSchemaRootField r a -> RemoteSchemaRootField r b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall r a b.
(a -> b) -> RemoteSchemaRootField r a -> RemoteSchemaRootField r b
fmap :: forall a b.
(a -> b) -> RemoteSchemaRootField r a -> RemoteSchemaRootField r b
$c<$ :: forall r a b.
a -> RemoteSchemaRootField r b -> RemoteSchemaRootField r a
<$ :: forall a b.
a -> RemoteSchemaRootField r b -> RemoteSchemaRootField r a
Functor, (forall m. Monoid m => RemoteSchemaRootField r m -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> RemoteSchemaRootField r a -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> RemoteSchemaRootField r a -> m)
-> (forall a b.
(a -> b -> b) -> b -> RemoteSchemaRootField r a -> b)
-> (forall a b.
(a -> b -> b) -> b -> RemoteSchemaRootField r a -> b)
-> (forall b a.
(b -> a -> b) -> b -> RemoteSchemaRootField r a -> b)
-> (forall b a.
(b -> a -> b) -> b -> RemoteSchemaRootField r a -> b)
-> (forall a. (a -> a -> a) -> RemoteSchemaRootField r a -> a)
-> (forall a. (a -> a -> a) -> RemoteSchemaRootField r a -> a)
-> (forall a. RemoteSchemaRootField r a -> [a])
-> (forall a. RemoteSchemaRootField r a -> Bool)
-> (forall a. RemoteSchemaRootField r a -> Int)
-> (forall a. Eq a => a -> RemoteSchemaRootField r a -> Bool)
-> (forall a. Ord a => RemoteSchemaRootField r a -> a)
-> (forall a. Ord a => RemoteSchemaRootField r a -> a)
-> (forall a. Num a => RemoteSchemaRootField r a -> a)
-> (forall a. Num a => RemoteSchemaRootField r a -> a)
-> Foldable (RemoteSchemaRootField r)
forall a. Eq a => a -> RemoteSchemaRootField r a -> Bool
forall a. Num a => RemoteSchemaRootField r a -> a
forall a. Ord a => RemoteSchemaRootField r a -> a
forall m. Monoid m => RemoteSchemaRootField r m -> m
forall a. RemoteSchemaRootField r a -> Bool
forall a. RemoteSchemaRootField r a -> Int
forall a. RemoteSchemaRootField r a -> [a]
forall a. (a -> a -> a) -> RemoteSchemaRootField r a -> a
forall r a. Eq a => a -> RemoteSchemaRootField r a -> Bool
forall r a. Num a => RemoteSchemaRootField r a -> a
forall r a. Ord a => RemoteSchemaRootField r a -> a
forall m a. Monoid m => (a -> m) -> RemoteSchemaRootField r a -> m
forall r m. Monoid m => RemoteSchemaRootField r m -> m
forall r a. RemoteSchemaRootField r a -> Bool
forall r a. RemoteSchemaRootField r a -> Int
forall r a. RemoteSchemaRootField r a -> [a]
forall b a. (b -> a -> b) -> b -> RemoteSchemaRootField r a -> b
forall a b. (a -> b -> b) -> b -> RemoteSchemaRootField r a -> b
forall r a. (a -> a -> a) -> RemoteSchemaRootField r a -> a
forall r m a.
Monoid m =>
(a -> m) -> RemoteSchemaRootField r a -> m
forall r b a. (b -> a -> b) -> b -> RemoteSchemaRootField r a -> b
forall r a b. (a -> b -> b) -> b -> RemoteSchemaRootField r 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 r m. Monoid m => RemoteSchemaRootField r m -> m
fold :: forall m. Monoid m => RemoteSchemaRootField r m -> m
$cfoldMap :: forall r m a.
Monoid m =>
(a -> m) -> RemoteSchemaRootField r a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> RemoteSchemaRootField r a -> m
$cfoldMap' :: forall r m a.
Monoid m =>
(a -> m) -> RemoteSchemaRootField r a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> RemoteSchemaRootField r a -> m
$cfoldr :: forall r a b. (a -> b -> b) -> b -> RemoteSchemaRootField r a -> b
foldr :: forall a b. (a -> b -> b) -> b -> RemoteSchemaRootField r a -> b
$cfoldr' :: forall r a b. (a -> b -> b) -> b -> RemoteSchemaRootField r a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> RemoteSchemaRootField r a -> b
$cfoldl :: forall r b a. (b -> a -> b) -> b -> RemoteSchemaRootField r a -> b
foldl :: forall b a. (b -> a -> b) -> b -> RemoteSchemaRootField r a -> b
$cfoldl' :: forall r b a. (b -> a -> b) -> b -> RemoteSchemaRootField r a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> RemoteSchemaRootField r a -> b
$cfoldr1 :: forall r a. (a -> a -> a) -> RemoteSchemaRootField r a -> a
foldr1 :: forall a. (a -> a -> a) -> RemoteSchemaRootField r a -> a
$cfoldl1 :: forall r a. (a -> a -> a) -> RemoteSchemaRootField r a -> a
foldl1 :: forall a. (a -> a -> a) -> RemoteSchemaRootField r a -> a
$ctoList :: forall r a. RemoteSchemaRootField r a -> [a]
toList :: forall a. RemoteSchemaRootField r a -> [a]
$cnull :: forall r a. RemoteSchemaRootField r a -> Bool
null :: forall a. RemoteSchemaRootField r a -> Bool
$clength :: forall r a. RemoteSchemaRootField r a -> Int
length :: forall a. RemoteSchemaRootField r a -> Int
$celem :: forall r a. Eq a => a -> RemoteSchemaRootField r a -> Bool
elem :: forall a. Eq a => a -> RemoteSchemaRootField r a -> Bool
$cmaximum :: forall r a. Ord a => RemoteSchemaRootField r a -> a
maximum :: forall a. Ord a => RemoteSchemaRootField r a -> a
$cminimum :: forall r a. Ord a => RemoteSchemaRootField r a -> a
minimum :: forall a. Ord a => RemoteSchemaRootField r a -> a
$csum :: forall r a. Num a => RemoteSchemaRootField r a -> a
sum :: forall a. Num a => RemoteSchemaRootField r a -> a
$cproduct :: forall r a. Num a => RemoteSchemaRootField r a -> a
product :: forall a. Num a => RemoteSchemaRootField r a -> a
Foldable, Functor (RemoteSchemaRootField r)
Foldable (RemoteSchemaRootField r)
Functor (RemoteSchemaRootField r)
-> Foldable (RemoteSchemaRootField r)
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> RemoteSchemaRootField r a -> f (RemoteSchemaRootField r b))
-> (forall (f :: * -> *) a.
Applicative f =>
RemoteSchemaRootField r (f a) -> f (RemoteSchemaRootField r a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> RemoteSchemaRootField r a -> m (RemoteSchemaRootField r b))
-> (forall (m :: * -> *) a.
Monad m =>
RemoteSchemaRootField r (m a) -> m (RemoteSchemaRootField r a))
-> Traversable (RemoteSchemaRootField r)
forall r. Functor (RemoteSchemaRootField r)
forall r. Foldable (RemoteSchemaRootField r)
forall r (m :: * -> *) a.
Monad m =>
RemoteSchemaRootField r (m a) -> m (RemoteSchemaRootField r a)
forall r (f :: * -> *) a.
Applicative f =>
RemoteSchemaRootField r (f a) -> f (RemoteSchemaRootField r a)
forall r (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> RemoteSchemaRootField r a -> m (RemoteSchemaRootField r b)
forall r (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> RemoteSchemaRootField r a -> f (RemoteSchemaRootField r 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 =>
RemoteSchemaRootField r (m a) -> m (RemoteSchemaRootField r a)
forall (f :: * -> *) a.
Applicative f =>
RemoteSchemaRootField r (f a) -> f (RemoteSchemaRootField r a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> RemoteSchemaRootField r a -> m (RemoteSchemaRootField r b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> RemoteSchemaRootField r a -> f (RemoteSchemaRootField r b)
$ctraverse :: forall r (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> RemoteSchemaRootField r a -> f (RemoteSchemaRootField r b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> RemoteSchemaRootField r a -> f (RemoteSchemaRootField r b)
$csequenceA :: forall r (f :: * -> *) a.
Applicative f =>
RemoteSchemaRootField r (f a) -> f (RemoteSchemaRootField r a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
RemoteSchemaRootField r (f a) -> f (RemoteSchemaRootField r a)
$cmapM :: forall r (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> RemoteSchemaRootField r a -> m (RemoteSchemaRootField r b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> RemoteSchemaRootField r a -> m (RemoteSchemaRootField r b)
$csequence :: forall r (m :: * -> *) a.
Monad m =>
RemoteSchemaRootField r (m a) -> m (RemoteSchemaRootField r a)
sequence :: forall (m :: * -> *) a.
Monad m =>
RemoteSchemaRootField r (m a) -> m (RemoteSchemaRootField r a)
Traversable)
data SchemaRemoteRelationshipSelect r = SchemaRemoteRelationshipSelect
{
forall r.
SchemaRemoteRelationshipSelect r -> HashMap FieldName Name
_srrsLHSJoinFields :: HashMap FieldName G.Name,
forall r. SchemaRemoteRelationshipSelect r -> r
_srrsRelationship :: r
}
deriving (SchemaRemoteRelationshipSelect r
-> SchemaRemoteRelationshipSelect r -> Bool
(SchemaRemoteRelationshipSelect r
-> SchemaRemoteRelationshipSelect r -> Bool)
-> (SchemaRemoteRelationshipSelect r
-> SchemaRemoteRelationshipSelect r -> Bool)
-> Eq (SchemaRemoteRelationshipSelect r)
forall r.
Eq r =>
SchemaRemoteRelationshipSelect r
-> SchemaRemoteRelationshipSelect r -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall r.
Eq r =>
SchemaRemoteRelationshipSelect r
-> SchemaRemoteRelationshipSelect r -> Bool
== :: SchemaRemoteRelationshipSelect r
-> SchemaRemoteRelationshipSelect r -> Bool
$c/= :: forall r.
Eq r =>
SchemaRemoteRelationshipSelect r
-> SchemaRemoteRelationshipSelect r -> Bool
/= :: SchemaRemoteRelationshipSelect r
-> SchemaRemoteRelationshipSelect r -> Bool
Eq, Int -> SchemaRemoteRelationshipSelect r -> ShowS
[SchemaRemoteRelationshipSelect r] -> ShowS
SchemaRemoteRelationshipSelect r -> String
(Int -> SchemaRemoteRelationshipSelect r -> ShowS)
-> (SchemaRemoteRelationshipSelect r -> String)
-> ([SchemaRemoteRelationshipSelect r] -> ShowS)
-> Show (SchemaRemoteRelationshipSelect r)
forall r.
Show r =>
Int -> SchemaRemoteRelationshipSelect r -> ShowS
forall r. Show r => [SchemaRemoteRelationshipSelect r] -> ShowS
forall r. Show r => SchemaRemoteRelationshipSelect r -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall r.
Show r =>
Int -> SchemaRemoteRelationshipSelect r -> ShowS
showsPrec :: Int -> SchemaRemoteRelationshipSelect r -> ShowS
$cshow :: forall r. Show r => SchemaRemoteRelationshipSelect r -> String
show :: SchemaRemoteRelationshipSelect r -> String
$cshowList :: forall r. Show r => [SchemaRemoteRelationshipSelect r] -> ShowS
showList :: [SchemaRemoteRelationshipSelect r] -> ShowS
Show, (forall a b.
(a -> b)
-> SchemaRemoteRelationshipSelect a
-> SchemaRemoteRelationshipSelect b)
-> (forall a b.
a
-> SchemaRemoteRelationshipSelect b
-> SchemaRemoteRelationshipSelect a)
-> Functor SchemaRemoteRelationshipSelect
forall a b.
a
-> SchemaRemoteRelationshipSelect b
-> SchemaRemoteRelationshipSelect a
forall a b.
(a -> b)
-> SchemaRemoteRelationshipSelect a
-> SchemaRemoteRelationshipSelect b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b.
(a -> b)
-> SchemaRemoteRelationshipSelect a
-> SchemaRemoteRelationshipSelect b
fmap :: forall a b.
(a -> b)
-> SchemaRemoteRelationshipSelect a
-> SchemaRemoteRelationshipSelect b
$c<$ :: forall a b.
a
-> SchemaRemoteRelationshipSelect b
-> SchemaRemoteRelationshipSelect a
<$ :: forall a b.
a
-> SchemaRemoteRelationshipSelect b
-> SchemaRemoteRelationshipSelect a
Functor, (forall m. Monoid m => SchemaRemoteRelationshipSelect m -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> SchemaRemoteRelationshipSelect a -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> SchemaRemoteRelationshipSelect a -> m)
-> (forall a b.
(a -> b -> b) -> b -> SchemaRemoteRelationshipSelect a -> b)
-> (forall a b.
(a -> b -> b) -> b -> SchemaRemoteRelationshipSelect a -> b)
-> (forall b a.
(b -> a -> b) -> b -> SchemaRemoteRelationshipSelect a -> b)
-> (forall b a.
(b -> a -> b) -> b -> SchemaRemoteRelationshipSelect a -> b)
-> (forall a.
(a -> a -> a) -> SchemaRemoteRelationshipSelect a -> a)
-> (forall a.
(a -> a -> a) -> SchemaRemoteRelationshipSelect a -> a)
-> (forall a. SchemaRemoteRelationshipSelect a -> [a])
-> (forall a. SchemaRemoteRelationshipSelect a -> Bool)
-> (forall a. SchemaRemoteRelationshipSelect a -> Int)
-> (forall a.
Eq a =>
a -> SchemaRemoteRelationshipSelect a -> Bool)
-> (forall a. Ord a => SchemaRemoteRelationshipSelect a -> a)
-> (forall a. Ord a => SchemaRemoteRelationshipSelect a -> a)
-> (forall a. Num a => SchemaRemoteRelationshipSelect a -> a)
-> (forall a. Num a => SchemaRemoteRelationshipSelect a -> a)
-> Foldable SchemaRemoteRelationshipSelect
forall a. Eq a => a -> SchemaRemoteRelationshipSelect a -> Bool
forall a. Num a => SchemaRemoteRelationshipSelect a -> a
forall a. Ord a => SchemaRemoteRelationshipSelect a -> a
forall m. Monoid m => SchemaRemoteRelationshipSelect m -> m
forall a. SchemaRemoteRelationshipSelect a -> Bool
forall a. SchemaRemoteRelationshipSelect a -> Int
forall a. SchemaRemoteRelationshipSelect a -> [a]
forall a. (a -> a -> a) -> SchemaRemoteRelationshipSelect a -> a
forall m a.
Monoid m =>
(a -> m) -> SchemaRemoteRelationshipSelect a -> m
forall b a.
(b -> a -> b) -> b -> SchemaRemoteRelationshipSelect a -> b
forall a b.
(a -> b -> b) -> b -> SchemaRemoteRelationshipSelect 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 m. Monoid m => SchemaRemoteRelationshipSelect m -> m
fold :: forall m. Monoid m => SchemaRemoteRelationshipSelect m -> m
$cfoldMap :: forall m a.
Monoid m =>
(a -> m) -> SchemaRemoteRelationshipSelect a -> m
foldMap :: forall m a.
Monoid m =>
(a -> m) -> SchemaRemoteRelationshipSelect a -> m
$cfoldMap' :: forall m a.
Monoid m =>
(a -> m) -> SchemaRemoteRelationshipSelect a -> m
foldMap' :: forall m a.
Monoid m =>
(a -> m) -> SchemaRemoteRelationshipSelect a -> m
$cfoldr :: forall a b.
(a -> b -> b) -> b -> SchemaRemoteRelationshipSelect a -> b
foldr :: forall a b.
(a -> b -> b) -> b -> SchemaRemoteRelationshipSelect a -> b
$cfoldr' :: forall a b.
(a -> b -> b) -> b -> SchemaRemoteRelationshipSelect a -> b
foldr' :: forall a b.
(a -> b -> b) -> b -> SchemaRemoteRelationshipSelect a -> b
$cfoldl :: forall b a.
(b -> a -> b) -> b -> SchemaRemoteRelationshipSelect a -> b
foldl :: forall b a.
(b -> a -> b) -> b -> SchemaRemoteRelationshipSelect a -> b
$cfoldl' :: forall b a.
(b -> a -> b) -> b -> SchemaRemoteRelationshipSelect a -> b
foldl' :: forall b a.
(b -> a -> b) -> b -> SchemaRemoteRelationshipSelect a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> SchemaRemoteRelationshipSelect a -> a
foldr1 :: forall a. (a -> a -> a) -> SchemaRemoteRelationshipSelect a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> SchemaRemoteRelationshipSelect a -> a
foldl1 :: forall a. (a -> a -> a) -> SchemaRemoteRelationshipSelect a -> a
$ctoList :: forall a. SchemaRemoteRelationshipSelect a -> [a]
toList :: forall a. SchemaRemoteRelationshipSelect a -> [a]
$cnull :: forall a. SchemaRemoteRelationshipSelect a -> Bool
null :: forall a. SchemaRemoteRelationshipSelect a -> Bool
$clength :: forall a. SchemaRemoteRelationshipSelect a -> Int
length :: forall a. SchemaRemoteRelationshipSelect a -> Int
$celem :: forall a. Eq a => a -> SchemaRemoteRelationshipSelect a -> Bool
elem :: forall a. Eq a => a -> SchemaRemoteRelationshipSelect a -> Bool
$cmaximum :: forall a. Ord a => SchemaRemoteRelationshipSelect a -> a
maximum :: forall a. Ord a => SchemaRemoteRelationshipSelect a -> a
$cminimum :: forall a. Ord a => SchemaRemoteRelationshipSelect a -> a
minimum :: forall a. Ord a => SchemaRemoteRelationshipSelect a -> a
$csum :: forall a. Num a => SchemaRemoteRelationshipSelect a -> a
sum :: forall a. Num a => SchemaRemoteRelationshipSelect a -> a
$cproduct :: forall a. Num a => SchemaRemoteRelationshipSelect a -> a
product :: forall a. Num a => SchemaRemoteRelationshipSelect a -> a
Foldable, Functor SchemaRemoteRelationshipSelect
Foldable SchemaRemoteRelationshipSelect
Functor SchemaRemoteRelationshipSelect
-> Foldable SchemaRemoteRelationshipSelect
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> SchemaRemoteRelationshipSelect a
-> f (SchemaRemoteRelationshipSelect b))
-> (forall (f :: * -> *) a.
Applicative f =>
SchemaRemoteRelationshipSelect (f a)
-> f (SchemaRemoteRelationshipSelect a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> SchemaRemoteRelationshipSelect a
-> m (SchemaRemoteRelationshipSelect b))
-> (forall (m :: * -> *) a.
Monad m =>
SchemaRemoteRelationshipSelect (m a)
-> m (SchemaRemoteRelationshipSelect a))
-> Traversable SchemaRemoteRelationshipSelect
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 =>
SchemaRemoteRelationshipSelect (m a)
-> m (SchemaRemoteRelationshipSelect a)
forall (f :: * -> *) a.
Applicative f =>
SchemaRemoteRelationshipSelect (f a)
-> f (SchemaRemoteRelationshipSelect a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> SchemaRemoteRelationshipSelect a
-> m (SchemaRemoteRelationshipSelect b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> SchemaRemoteRelationshipSelect a
-> f (SchemaRemoteRelationshipSelect b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> SchemaRemoteRelationshipSelect a
-> f (SchemaRemoteRelationshipSelect b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> SchemaRemoteRelationshipSelect a
-> f (SchemaRemoteRelationshipSelect b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
SchemaRemoteRelationshipSelect (f a)
-> f (SchemaRemoteRelationshipSelect a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
SchemaRemoteRelationshipSelect (f a)
-> f (SchemaRemoteRelationshipSelect a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> SchemaRemoteRelationshipSelect a
-> m (SchemaRemoteRelationshipSelect b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> SchemaRemoteRelationshipSelect a
-> m (SchemaRemoteRelationshipSelect b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
SchemaRemoteRelationshipSelect (m a)
-> m (SchemaRemoteRelationshipSelect a)
sequence :: forall (m :: * -> *) a.
Monad m =>
SchemaRemoteRelationshipSelect (m a)
-> m (SchemaRemoteRelationshipSelect a)
Traversable)
data RemoteFieldArgument = RemoteFieldArgument
{ RemoteFieldArgument -> Name
_rfaArgument :: G.Name,
RemoteFieldArgument -> InputValue RemoteSchemaVariable
_rfaValue :: InputValue RemoteSchemaVariable
}
deriving (RemoteFieldArgument -> RemoteFieldArgument -> Bool
(RemoteFieldArgument -> RemoteFieldArgument -> Bool)
-> (RemoteFieldArgument -> RemoteFieldArgument -> Bool)
-> Eq RemoteFieldArgument
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RemoteFieldArgument -> RemoteFieldArgument -> Bool
== :: RemoteFieldArgument -> RemoteFieldArgument -> Bool
$c/= :: RemoteFieldArgument -> RemoteFieldArgument -> Bool
/= :: RemoteFieldArgument -> RemoteFieldArgument -> Bool
Eq, Int -> RemoteFieldArgument -> ShowS
[RemoteFieldArgument] -> ShowS
RemoteFieldArgument -> String
(Int -> RemoteFieldArgument -> ShowS)
-> (RemoteFieldArgument -> String)
-> ([RemoteFieldArgument] -> ShowS)
-> Show RemoteFieldArgument
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RemoteFieldArgument -> ShowS
showsPrec :: Int -> RemoteFieldArgument -> ShowS
$cshow :: RemoteFieldArgument -> String
show :: RemoteFieldArgument -> String
$cshowList :: [RemoteFieldArgument] -> ShowS
showList :: [RemoteFieldArgument] -> ShowS
Show)
data RemoteSchemaSelect r = RemoteSchemaSelect
{ forall r. RemoteSchemaSelect r -> [RemoteFieldArgument]
_rselArgs :: [RemoteFieldArgument],
forall r. RemoteSchemaSelect r -> ResultCustomizer
_rselResultCustomizer :: ResultCustomizer,
forall r.
RemoteSchemaSelect r -> SelectionSet r RemoteSchemaVariable
_rselSelection :: SelectionSet r RemoteSchemaVariable,
forall r. RemoteSchemaSelect r -> NonEmpty FieldCall
_rselFieldCall :: NonEmpty FieldCall,
forall r. RemoteSchemaSelect r -> RemoteSchemaInfo
_rselRemoteSchema :: RemoteSchemaInfo
}
deriving (Int -> RemoteSchemaSelect r -> ShowS
[RemoteSchemaSelect r] -> ShowS
RemoteSchemaSelect r -> String
(Int -> RemoteSchemaSelect r -> ShowS)
-> (RemoteSchemaSelect r -> String)
-> ([RemoteSchemaSelect r] -> ShowS)
-> Show (RemoteSchemaSelect r)
forall r. Show r => Int -> RemoteSchemaSelect r -> ShowS
forall r. Show r => [RemoteSchemaSelect r] -> ShowS
forall r. Show r => RemoteSchemaSelect r -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall r. Show r => Int -> RemoteSchemaSelect r -> ShowS
showsPrec :: Int -> RemoteSchemaSelect r -> ShowS
$cshow :: forall r. Show r => RemoteSchemaSelect r -> String
show :: RemoteSchemaSelect r -> String
$cshowList :: forall r. Show r => [RemoteSchemaSelect r] -> ShowS
showList :: [RemoteSchemaSelect r] -> ShowS
Show)
convertSelectionSet ::
forall var.
(Eq var) =>
SelectionSet Void var ->
G.SelectionSet G.NoFragments var
convertSelectionSet :: forall var.
Eq var =>
SelectionSet Void var -> SelectionSet NoFragments var
convertSelectionSet = \case
SelectionSetObject ObjectSelectionSet Void var
s -> ObjectSelectionSet Void var -> [Selection NoFragments var]
convertObjectSelectionSet ObjectSelectionSet Void var
s
SelectionSetUnion DeduplicatedSelectionSet Void var
s -> DeduplicatedSelectionSet Void var -> [Selection NoFragments var]
convertAbstractTypeSelectionSet DeduplicatedSelectionSet Void var
s
SelectionSetInterface DeduplicatedSelectionSet Void var
s -> DeduplicatedSelectionSet Void var -> [Selection NoFragments var]
convertAbstractTypeSelectionSet DeduplicatedSelectionSet Void var
s
SelectionSet Void var
SelectionSetNone -> [Selection NoFragments var]
forall a. Monoid a => a
mempty
where
convertField :: Field Void var -> G.Field G.NoFragments var
convertField :: Field Void var -> Field NoFragments var
convertField = \case
FieldGraphQL GraphQLField Void var
f -> GraphQLField Void var -> Field NoFragments var
forall var.
Eq var =>
GraphQLField Void var -> Field NoFragments var
convertGraphQLField GraphQLField Void var
f
convertObjectSelectionSet :: ObjectSelectionSet Void var -> [Selection NoFragments var]
convertObjectSelectionSet =
((Name, Field Void var) -> Selection NoFragments var)
-> [(Name, Field Void var)] -> [Selection NoFragments var]
forall a b. (a -> b) -> [a] -> [b]
map (Field NoFragments var -> Selection NoFragments var
forall (frag :: * -> *) var. Field frag var -> Selection frag var
G.SelectionField (Field NoFragments var -> Selection NoFragments var)
-> ((Name, Field Void var) -> Field NoFragments var)
-> (Name, Field Void var)
-> Selection NoFragments var
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Field Void var -> Field NoFragments var
convertField (Field Void var -> Field NoFragments var)
-> ((Name, Field Void var) -> Field Void var)
-> (Name, Field Void var)
-> Field NoFragments var
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name, Field Void var) -> Field Void var
forall a b. (a, b) -> b
snd) ([(Name, Field Void var)] -> [Selection NoFragments var])
-> (ObjectSelectionSet Void var -> [(Name, Field Void var)])
-> ObjectSelectionSet Void var
-> [Selection NoFragments var]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ObjectSelectionSet Void var -> [(Name, Field Void var)]
forall k v. InsOrdHashMap k v -> [(k, v)]
InsOrdHashMap.toList
convertAbstractTypeSelectionSet :: DeduplicatedSelectionSet Void var -> [Selection NoFragments var]
convertAbstractTypeSelectionSet DeduplicatedSelectionSet Void var
abstractSelectionSet =
let (ObjectSelectionSet Void var
base, HashMap Name (ObjectSelectionSet Void var)
members) = DeduplicatedSelectionSet Void var
-> (ObjectSelectionSet Void var,
HashMap Name (ObjectSelectionSet Void var))
forall var.
Eq var =>
DeduplicatedSelectionSet Void var
-> (ObjectSelectionSet Void var,
HashMap Name (ObjectSelectionSet Void var))
reduceAbstractTypeSelectionSet DeduplicatedSelectionSet Void var
abstractSelectionSet
commonFields :: [Selection NoFragments var]
commonFields = ObjectSelectionSet Void var -> [Selection NoFragments var]
convertObjectSelectionSet ObjectSelectionSet Void var
base
concreteTypeSelectionSets :: [InlineFragment NoFragments var]
concreteTypeSelectionSets =
HashMap Name (ObjectSelectionSet Void var)
-> [(Name, ObjectSelectionSet Void var)]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList HashMap Name (ObjectSelectionSet Void var)
members [(Name, ObjectSelectionSet Void var)]
-> ((Name, ObjectSelectionSet Void var)
-> InlineFragment NoFragments var)
-> [InlineFragment NoFragments var]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \(Name
concreteType, ObjectSelectionSet Void var
selectionSet) ->
G.InlineFragment
{ _ifTypeCondition :: Maybe Name
G._ifTypeCondition = Name -> Maybe Name
forall a. a -> Maybe a
Just Name
concreteType,
_ifDirectives :: [Directive var]
G._ifDirectives = [Directive var]
forall a. Monoid a => a
mempty,
_ifSelectionSet :: [Selection NoFragments var]
G._ifSelectionSet = ObjectSelectionSet Void var -> [Selection NoFragments var]
convertObjectSelectionSet ObjectSelectionSet Void var
selectionSet
}
in
[Selection NoFragments var]
commonFields [Selection NoFragments var]
-> [Selection NoFragments var] -> [Selection NoFragments var]
forall a. Semigroup a => a -> a -> a
<> (InlineFragment NoFragments var -> Selection NoFragments var)
-> [InlineFragment NoFragments var] -> [Selection NoFragments var]
forall a b. (a -> b) -> [a] -> [b]
map InlineFragment NoFragments var -> Selection NoFragments var
forall (frag :: * -> *) var.
InlineFragment frag var -> Selection frag var
G.SelectionInlineFragment [InlineFragment NoFragments var]
concreteTypeSelectionSets
convertGraphQLField :: (Eq var) => GraphQLField Void var -> G.Field G.NoFragments var
convertGraphQLField :: forall var.
Eq var =>
GraphQLField Void var -> Field NoFragments var
convertGraphQLField GraphQLField {[Directive var]
HashMap Name (Value var)
Name
SelectionSet Void var
_fAlias :: forall r var. GraphQLField r var -> Name
_fName :: forall r var. GraphQLField r var -> Name
_fArguments :: forall r var. GraphQLField r var -> HashMap Name (Value var)
_fDirectives :: forall r var. GraphQLField r var -> [Directive var]
_fSelectionSet :: forall r var. GraphQLField r var -> SelectionSet r var
_fAlias :: Name
_fName :: Name
_fArguments :: HashMap Name (Value var)
_fDirectives :: [Directive var]
_fSelectionSet :: SelectionSet Void var
..} =
G.Field
{
_fAlias :: Maybe Name
G._fAlias = if Name
_fAlias Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
/= Name
_fName then Name -> Maybe Name
forall a. a -> Maybe a
Just Name
_fAlias else Maybe Name
forall a. Maybe a
Nothing,
_fName :: Name
G._fName = Name
_fName,
_fArguments :: HashMap Name (Value var)
G._fArguments = HashMap Name (Value var)
_fArguments,
_fDirectives :: [Directive var]
G._fDirectives = [Directive var]
forall a. Monoid a => a
mempty,
_fSelectionSet :: SelectionSet NoFragments var
G._fSelectionSet = SelectionSet Void var -> SelectionSet NoFragments var
forall var.
Eq var =>
SelectionSet Void var -> SelectionSet NoFragments var
convertSelectionSet SelectionSet Void var
_fSelectionSet
}
reduceAbstractTypeSelectionSet ::
(Eq var) =>
DeduplicatedSelectionSet Void var ->
(ObjectSelectionSet Void var, HashMap.HashMap G.Name (ObjectSelectionSet Void var))
reduceAbstractTypeSelectionSet :: forall var.
Eq var =>
DeduplicatedSelectionSet Void var
-> (ObjectSelectionSet Void var,
HashMap Name (ObjectSelectionSet Void var))
reduceAbstractTypeSelectionSet (DeduplicatedSelectionSet HashSet Name
baseMemberFields HashMap Name (ObjectSelectionSet Void var)
selectionSets) =
(ObjectSelectionSet Void var
baseSelectionSet, [(Name, ObjectSelectionSet Void var)]
-> HashMap Name (ObjectSelectionSet Void var)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList [(Name, ObjectSelectionSet Void var)]
memberSelectionSets)
where
sharedSelectionSetPrefix :: [(Name, Field Void var)]
sharedSelectionSetPrefix = [[(Name, Field Void var)]] -> [(Name, Field Void var)]
forall a. Eq a => [[a]] -> [a]
longestCommonPrefix ([[(Name, Field Void var)]] -> [(Name, Field Void var)])
-> [[(Name, Field Void var)]] -> [(Name, Field Void var)]
forall a b. (a -> b) -> a -> b
$ ((Name, ObjectSelectionSet Void var) -> [(Name, Field Void var)])
-> [(Name, ObjectSelectionSet Void var)]
-> [[(Name, Field Void var)]]
forall a b. (a -> b) -> [a] -> [b]
map (ObjectSelectionSet Void var -> [(Name, Field Void var)]
forall k v. InsOrdHashMap k v -> [(k, v)]
InsOrdHashMap.toList (ObjectSelectionSet Void var -> [(Name, Field Void var)])
-> ((Name, ObjectSelectionSet Void var)
-> ObjectSelectionSet Void var)
-> (Name, ObjectSelectionSet Void var)
-> [(Name, Field Void var)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name, ObjectSelectionSet Void var) -> ObjectSelectionSet Void var
forall a b. (a, b) -> b
snd) ([(Name, ObjectSelectionSet Void var)]
-> [[(Name, Field Void var)]])
-> [(Name, ObjectSelectionSet Void var)]
-> [[(Name, Field Void var)]]
forall a b. (a -> b) -> a -> b
$ HashMap Name (ObjectSelectionSet Void var)
-> [(Name, ObjectSelectionSet Void var)]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList HashMap Name (ObjectSelectionSet Void var)
selectionSets
baseSelectionSet :: ObjectSelectionSet Void var
baseSelectionSet = [(Name, Field Void var)] -> ObjectSelectionSet Void var
forall k v. (Eq k, Hashable k) => [(k, v)] -> InsOrdHashMap k v
InsOrdHashMap.fromList ([(Name, Field Void var)] -> ObjectSelectionSet Void var)
-> [(Name, Field Void var)] -> ObjectSelectionSet Void var
forall a b. (a -> b) -> a -> b
$ ((Name, Field Void var) -> Bool)
-> [(Name, Field Void var)] -> [(Name, Field Void var)]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Field Void var -> Bool
shouldAddToBase (Field Void var -> Bool)
-> ((Name, Field Void var) -> Field Void var)
-> (Name, Field Void var)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name, Field Void var) -> Field Void var
forall a b. (a, b) -> b
snd) [(Name, Field Void var)]
sharedSelectionSetPrefix
shouldAddToBase :: Field Void var -> Bool
shouldAddToBase = \case
FieldGraphQL GraphQLField Void var
f -> Name -> HashSet Name -> Bool
forall a. (Eq a, Hashable a) => a -> HashSet a -> Bool
Set.member (GraphQLField Void var -> Name
forall r var. GraphQLField r var -> Name
_fName GraphQLField Void var
f) HashSet Name
baseMemberFields
memberSelectionSets :: [(Name, ObjectSelectionSet Void var)]
memberSelectionSets =
((Name, ObjectSelectionSet Void var) -> Bool)
-> [(Name, ObjectSelectionSet Void var)]
-> [(Name, ObjectSelectionSet Void var)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> ((Name, ObjectSelectionSet Void var) -> Bool)
-> (Name, ObjectSelectionSet Void var)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ObjectSelectionSet Void var -> Bool
forall a. InsOrdHashMap Name a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (ObjectSelectionSet Void var -> Bool)
-> ((Name, ObjectSelectionSet Void var)
-> ObjectSelectionSet Void var)
-> (Name, ObjectSelectionSet Void var)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name, ObjectSelectionSet Void var) -> ObjectSelectionSet Void var
forall a b. (a, b) -> b
snd)
([(Name, ObjectSelectionSet Void var)]
-> [(Name, ObjectSelectionSet Void var)])
-> [(Name, ObjectSelectionSet Void var)]
-> [(Name, ObjectSelectionSet Void var)]
forall a b. (a -> b) -> a -> b
$
((Name, ObjectSelectionSet Void var)
-> (Name, ObjectSelectionSet Void var))
-> [(Name, ObjectSelectionSet Void var)]
-> [(Name, ObjectSelectionSet Void var)]
forall a b. (a -> b) -> [a] -> [b]
map ((ObjectSelectionSet Void var -> ObjectSelectionSet Void var)
-> (Name, ObjectSelectionSet Void var)
-> (Name, ObjectSelectionSet Void var)
forall b c d. (b -> c) -> (d, b) -> (d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second ([(Name, Field Void var)] -> ObjectSelectionSet Void var
forall k v. (Eq k, Hashable k) => [(k, v)] -> InsOrdHashMap k v
InsOrdHashMap.fromList ([(Name, Field Void var)] -> ObjectSelectionSet Void var)
-> (ObjectSelectionSet Void var -> [(Name, Field Void var)])
-> ObjectSelectionSet Void var
-> ObjectSelectionSet Void var
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [(Name, Field Void var)] -> [(Name, Field Void var)]
forall a. Int -> [a] -> [a]
drop (ObjectSelectionSet Void var -> Int
forall k v. InsOrdHashMap k v -> Int
InsOrdHashMap.size ObjectSelectionSet Void var
baseSelectionSet) ([(Name, Field Void var)] -> [(Name, Field Void var)])
-> (ObjectSelectionSet Void var -> [(Name, Field Void var)])
-> ObjectSelectionSet Void var
-> [(Name, Field Void var)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ObjectSelectionSet Void var -> [(Name, Field Void var)]
forall k v. InsOrdHashMap k v -> [(k, v)]
InsOrdHashMap.toList))
([(Name, ObjectSelectionSet Void var)]
-> [(Name, ObjectSelectionSet Void var)])
-> [(Name, ObjectSelectionSet Void var)]
-> [(Name, ObjectSelectionSet Void var)]
forall a b. (a -> b) -> a -> b
$ HashMap Name (ObjectSelectionSet Void var)
-> [(Name, ObjectSelectionSet Void var)]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList HashMap Name (ObjectSelectionSet Void var)
selectionSets
$(makePrisms ''Field)
$(makeLenses ''GraphQLField)
$(makeLenses ''DeduplicatedSelectionSet)