module Hasura.GraphQL.Transport.HTTP.Protocol
( GQLReq (..),
GQLBatchedReqs (..),
GQLReqUnparsed,
GQLReqParsed,
GQLReqOutgoing,
renderGQLReqOutgoing,
SingleOperation,
getSingleOperation,
toParsed,
getOpNameFromParsedReq,
GQLQueryText (..),
GQLExecDoc (..),
OperationName (..),
VariableValues,
encodeGQErr,
encodeGQExecError,
encodeGQResp,
decodeGQResp,
encodeHTTPResp,
GQResult,
GQExecError (..),
GQResponse,
isExecError,
ReqsText,
)
where
import Data.Aeson qualified as J
import Data.Aeson.Casing qualified as J
import Data.Aeson.Encoding qualified as J
import Data.Aeson.KeyMap qualified as KM
import Data.ByteString.Lazy qualified as BL
import Data.Either (isLeft)
import Data.HashMap.Strict qualified as HashMap
import Data.Text.Extended (dquote)
import Hasura.Base.Error
import Hasura.Base.Instances ()
import Hasura.EncJSON
import Hasura.GraphQL.Execute.Inline qualified as EI
import Hasura.Prelude
import Language.GraphQL.Draft.Parser qualified as G
import Language.GraphQL.Draft.Printer qualified as G
import Language.GraphQL.Draft.Syntax qualified as G
import Language.Haskell.TH.Syntax (Lift)
newtype GQLExecDoc = GQLExecDoc {GQLExecDoc -> [ExecutableDefinition Name]
unGQLExecDoc :: [G.ExecutableDefinition G.Name]}
deriving (Eq GQLExecDoc
Eq GQLExecDoc
-> (GQLExecDoc -> GQLExecDoc -> Ordering)
-> (GQLExecDoc -> GQLExecDoc -> Bool)
-> (GQLExecDoc -> GQLExecDoc -> Bool)
-> (GQLExecDoc -> GQLExecDoc -> Bool)
-> (GQLExecDoc -> GQLExecDoc -> Bool)
-> (GQLExecDoc -> GQLExecDoc -> GQLExecDoc)
-> (GQLExecDoc -> GQLExecDoc -> GQLExecDoc)
-> Ord GQLExecDoc
GQLExecDoc -> GQLExecDoc -> Bool
GQLExecDoc -> GQLExecDoc -> Ordering
GQLExecDoc -> GQLExecDoc -> GQLExecDoc
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
$ccompare :: GQLExecDoc -> GQLExecDoc -> Ordering
compare :: GQLExecDoc -> GQLExecDoc -> Ordering
$c< :: GQLExecDoc -> GQLExecDoc -> Bool
< :: GQLExecDoc -> GQLExecDoc -> Bool
$c<= :: GQLExecDoc -> GQLExecDoc -> Bool
<= :: GQLExecDoc -> GQLExecDoc -> Bool
$c> :: GQLExecDoc -> GQLExecDoc -> Bool
> :: GQLExecDoc -> GQLExecDoc -> Bool
$c>= :: GQLExecDoc -> GQLExecDoc -> Bool
>= :: GQLExecDoc -> GQLExecDoc -> Bool
$cmax :: GQLExecDoc -> GQLExecDoc -> GQLExecDoc
max :: GQLExecDoc -> GQLExecDoc -> GQLExecDoc
$cmin :: GQLExecDoc -> GQLExecDoc -> GQLExecDoc
min :: GQLExecDoc -> GQLExecDoc -> GQLExecDoc
Ord, Int -> GQLExecDoc -> ShowS
[GQLExecDoc] -> ShowS
GQLExecDoc -> String
(Int -> GQLExecDoc -> ShowS)
-> (GQLExecDoc -> String)
-> ([GQLExecDoc] -> ShowS)
-> Show GQLExecDoc
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GQLExecDoc -> ShowS
showsPrec :: Int -> GQLExecDoc -> ShowS
$cshow :: GQLExecDoc -> String
show :: GQLExecDoc -> String
$cshowList :: [GQLExecDoc] -> ShowS
showList :: [GQLExecDoc] -> ShowS
Show, GQLExecDoc -> GQLExecDoc -> Bool
(GQLExecDoc -> GQLExecDoc -> Bool)
-> (GQLExecDoc -> GQLExecDoc -> Bool) -> Eq GQLExecDoc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GQLExecDoc -> GQLExecDoc -> Bool
== :: GQLExecDoc -> GQLExecDoc -> Bool
$c/= :: GQLExecDoc -> GQLExecDoc -> Bool
/= :: GQLExecDoc -> GQLExecDoc -> Bool
Eq, Eq GQLExecDoc
Eq GQLExecDoc
-> (Int -> GQLExecDoc -> Int)
-> (GQLExecDoc -> Int)
-> Hashable GQLExecDoc
Int -> GQLExecDoc -> Int
GQLExecDoc -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> GQLExecDoc -> Int
hashWithSalt :: Int -> GQLExecDoc -> Int
$chash :: GQLExecDoc -> Int
hash :: GQLExecDoc -> Int
Hashable, (forall (m :: * -> *). Quote m => GQLExecDoc -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
GQLExecDoc -> Code m GQLExecDoc)
-> Lift GQLExecDoc
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => GQLExecDoc -> m Exp
forall (m :: * -> *). Quote m => GQLExecDoc -> Code m GQLExecDoc
$clift :: forall (m :: * -> *). Quote m => GQLExecDoc -> m Exp
lift :: forall (m :: * -> *). Quote m => GQLExecDoc -> m Exp
$cliftTyped :: forall (m :: * -> *). Quote m => GQLExecDoc -> Code m GQLExecDoc
liftTyped :: forall (m :: * -> *). Quote m => GQLExecDoc -> Code m GQLExecDoc
Lift)
instance J.FromJSON GQLExecDoc where
parseJSON :: Value -> Parser GQLExecDoc
parseJSON Value
v = [ExecutableDefinition Name] -> GQLExecDoc
GQLExecDoc ([ExecutableDefinition Name] -> GQLExecDoc)
-> (ExecutableDocument Name -> [ExecutableDefinition Name])
-> ExecutableDocument Name
-> GQLExecDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExecutableDocument Name -> [ExecutableDefinition Name]
forall var. ExecutableDocument var -> [ExecutableDefinition var]
G.getExecutableDefinitions (ExecutableDocument Name -> GQLExecDoc)
-> Parser (ExecutableDocument Name) -> Parser GQLExecDoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (ExecutableDocument Name)
forall a. FromJSON a => Value -> Parser a
J.parseJSON Value
v
instance J.ToJSON GQLExecDoc where
toJSON :: GQLExecDoc -> Value
toJSON = ExecutableDocument Name -> Value
forall a. ToJSON a => a -> Value
J.toJSON (ExecutableDocument Name -> Value)
-> (GQLExecDoc -> ExecutableDocument Name) -> GQLExecDoc -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ExecutableDefinition Name] -> ExecutableDocument Name
forall var. [ExecutableDefinition var] -> ExecutableDocument var
G.ExecutableDocument ([ExecutableDefinition Name] -> ExecutableDocument Name)
-> (GQLExecDoc -> [ExecutableDefinition Name])
-> GQLExecDoc
-> ExecutableDocument Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GQLExecDoc -> [ExecutableDefinition Name]
unGQLExecDoc
newtype OperationName = OperationName {OperationName -> Name
_unOperationName :: G.Name}
deriving (Eq OperationName
Eq OperationName
-> (OperationName -> OperationName -> Ordering)
-> (OperationName -> OperationName -> Bool)
-> (OperationName -> OperationName -> Bool)
-> (OperationName -> OperationName -> Bool)
-> (OperationName -> OperationName -> Bool)
-> (OperationName -> OperationName -> OperationName)
-> (OperationName -> OperationName -> OperationName)
-> Ord OperationName
OperationName -> OperationName -> Bool
OperationName -> OperationName -> Ordering
OperationName -> OperationName -> OperationName
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
$ccompare :: OperationName -> OperationName -> Ordering
compare :: OperationName -> OperationName -> Ordering
$c< :: OperationName -> OperationName -> Bool
< :: OperationName -> OperationName -> Bool
$c<= :: OperationName -> OperationName -> Bool
<= :: OperationName -> OperationName -> Bool
$c> :: OperationName -> OperationName -> Bool
> :: OperationName -> OperationName -> Bool
$c>= :: OperationName -> OperationName -> Bool
>= :: OperationName -> OperationName -> Bool
$cmax :: OperationName -> OperationName -> OperationName
max :: OperationName -> OperationName -> OperationName
$cmin :: OperationName -> OperationName -> OperationName
min :: OperationName -> OperationName -> OperationName
Ord, Int -> OperationName -> ShowS
[OperationName] -> ShowS
OperationName -> String
(Int -> OperationName -> ShowS)
-> (OperationName -> String)
-> ([OperationName] -> ShowS)
-> Show OperationName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OperationName -> ShowS
showsPrec :: Int -> OperationName -> ShowS
$cshow :: OperationName -> String
show :: OperationName -> String
$cshowList :: [OperationName] -> ShowS
showList :: [OperationName] -> ShowS
Show, OperationName -> OperationName -> Bool
(OperationName -> OperationName -> Bool)
-> (OperationName -> OperationName -> Bool) -> Eq OperationName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OperationName -> OperationName -> Bool
== :: OperationName -> OperationName -> Bool
$c/= :: OperationName -> OperationName -> Bool
/= :: OperationName -> OperationName -> Bool
Eq, Eq OperationName
Eq OperationName
-> (Int -> OperationName -> Int)
-> (OperationName -> Int)
-> Hashable OperationName
Int -> OperationName -> Int
OperationName -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> OperationName -> Int
hashWithSalt :: Int -> OperationName -> Int
$chash :: OperationName -> Int
hash :: OperationName -> Int
Hashable, [OperationName] -> Value
[OperationName] -> Encoding
OperationName -> Value
OperationName -> Encoding
(OperationName -> Value)
-> (OperationName -> Encoding)
-> ([OperationName] -> Value)
-> ([OperationName] -> Encoding)
-> ToJSON OperationName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: OperationName -> Value
toJSON :: OperationName -> Value
$ctoEncoding :: OperationName -> Encoding
toEncoding :: OperationName -> Encoding
$ctoJSONList :: [OperationName] -> Value
toJSONList :: [OperationName] -> Value
$ctoEncodingList :: [OperationName] -> Encoding
toEncodingList :: [OperationName] -> Encoding
J.ToJSON, (forall (m :: * -> *). Quote m => OperationName -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
OperationName -> Code m OperationName)
-> Lift OperationName
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => OperationName -> m Exp
forall (m :: * -> *).
Quote m =>
OperationName -> Code m OperationName
$clift :: forall (m :: * -> *). Quote m => OperationName -> m Exp
lift :: forall (m :: * -> *). Quote m => OperationName -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
OperationName -> Code m OperationName
liftTyped :: forall (m :: * -> *).
Quote m =>
OperationName -> Code m OperationName
Lift)
instance J.FromJSON OperationName where
parseJSON :: Value -> Parser OperationName
parseJSON Value
v = Name -> OperationName
OperationName (Name -> OperationName) -> Parser Name -> Parser OperationName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Name
forall a. FromJSON a => Value -> Parser a
J.parseJSON Value
v
type VariableValues = HashMap.HashMap G.Name J.Value
data GQLReq a = GQLReq
{ forall a. GQLReq a -> Maybe OperationName
_grOperationName :: !(Maybe OperationName),
forall a. GQLReq a -> a
_grQuery :: !a,
forall a. GQLReq a -> Maybe VariableValues
_grVariables :: !(Maybe VariableValues)
}
deriving (Int -> GQLReq a -> ShowS
[GQLReq a] -> ShowS
GQLReq a -> String
(Int -> GQLReq a -> ShowS)
-> (GQLReq a -> String) -> ([GQLReq a] -> ShowS) -> Show (GQLReq a)
forall a. Show a => Int -> GQLReq a -> ShowS
forall a. Show a => [GQLReq a] -> ShowS
forall a. Show a => GQLReq a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> GQLReq a -> ShowS
showsPrec :: Int -> GQLReq a -> ShowS
$cshow :: forall a. Show a => GQLReq a -> String
show :: GQLReq a -> String
$cshowList :: forall a. Show a => [GQLReq a] -> ShowS
showList :: [GQLReq a] -> ShowS
Show, GQLReq a -> GQLReq a -> Bool
(GQLReq a -> GQLReq a -> Bool)
-> (GQLReq a -> GQLReq a -> Bool) -> Eq (GQLReq a)
forall a. Eq a => GQLReq a -> GQLReq a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => GQLReq a -> GQLReq a -> Bool
== :: GQLReq a -> GQLReq a -> Bool
$c/= :: forall a. Eq a => GQLReq a -> GQLReq a -> Bool
/= :: GQLReq a -> GQLReq a -> Bool
Eq, (forall x. GQLReq a -> Rep (GQLReq a) x)
-> (forall x. Rep (GQLReq a) x -> GQLReq a) -> Generic (GQLReq a)
forall x. Rep (GQLReq a) x -> GQLReq a
forall x. GQLReq a -> Rep (GQLReq a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (GQLReq a) x -> GQLReq a
forall a x. GQLReq a -> Rep (GQLReq a) x
$cfrom :: forall a x. GQLReq a -> Rep (GQLReq a) x
from :: forall x. GQLReq a -> Rep (GQLReq a) x
$cto :: forall a x. Rep (GQLReq a) x -> GQLReq a
to :: forall x. Rep (GQLReq a) x -> GQLReq a
Generic, (forall a b. (a -> b) -> GQLReq a -> GQLReq b)
-> (forall a b. a -> GQLReq b -> GQLReq a) -> Functor GQLReq
forall a b. a -> GQLReq b -> GQLReq a
forall a b. (a -> b) -> GQLReq a -> GQLReq 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) -> GQLReq a -> GQLReq b
fmap :: forall a b. (a -> b) -> GQLReq a -> GQLReq b
$c<$ :: forall a b. a -> GQLReq b -> GQLReq a
<$ :: forall a b. a -> GQLReq b -> GQLReq a
Functor, (forall (m :: * -> *). Quote m => GQLReq a -> m Exp)
-> (forall (m :: * -> *). Quote m => GQLReq a -> Code m (GQLReq a))
-> Lift (GQLReq a)
forall a (m :: * -> *). (Lift a, Quote m) => GQLReq a -> m Exp
forall a (m :: * -> *).
(Lift a, Quote m) =>
GQLReq a -> Code m (GQLReq a)
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => GQLReq a -> m Exp
forall (m :: * -> *). Quote m => GQLReq a -> Code m (GQLReq a)
$clift :: forall a (m :: * -> *). (Lift a, Quote m) => GQLReq a -> m Exp
lift :: forall (m :: * -> *). Quote m => GQLReq a -> m Exp
$cliftTyped :: forall a (m :: * -> *).
(Lift a, Quote m) =>
GQLReq a -> Code m (GQLReq a)
liftTyped :: forall (m :: * -> *). Quote m => GQLReq a -> Code m (GQLReq a)
Lift)
instance (J.FromJSON a) => J.FromJSON (GQLReq a) where
parseJSON :: Value -> Parser (GQLReq a)
parseJSON = Options -> Value -> Parser (GQLReq a)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
J.genericParseJSON (ShowS -> Options
J.aesonPrefix ShowS
J.camelCase) {omitNothingFields :: Bool
J.omitNothingFields = Bool
True}
instance (J.ToJSON a) => J.ToJSON (GQLReq a) where
toJSON :: GQLReq a -> Value
toJSON = Options -> GQLReq a -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
J.genericToJSON (ShowS -> Options
J.aesonPrefix ShowS
J.camelCase) {omitNothingFields :: Bool
J.omitNothingFields = Bool
True}
toEncoding :: GQLReq a -> Encoding
toEncoding = Options -> GQLReq a -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
J.genericToEncoding (ShowS -> Options
J.aesonPrefix ShowS
J.camelCase) {omitNothingFields :: Bool
J.omitNothingFields = Bool
True}
instance (Hashable a) => Hashable (GQLReq a)
data GQLBatchedReqs a
= GQLSingleRequest a
| GQLBatchedReqs [a]
deriving (Int -> GQLBatchedReqs a -> ShowS
[GQLBatchedReqs a] -> ShowS
GQLBatchedReqs a -> String
(Int -> GQLBatchedReqs a -> ShowS)
-> (GQLBatchedReqs a -> String)
-> ([GQLBatchedReqs a] -> ShowS)
-> Show (GQLBatchedReqs a)
forall a. Show a => Int -> GQLBatchedReqs a -> ShowS
forall a. Show a => [GQLBatchedReqs a] -> ShowS
forall a. Show a => GQLBatchedReqs a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> GQLBatchedReqs a -> ShowS
showsPrec :: Int -> GQLBatchedReqs a -> ShowS
$cshow :: forall a. Show a => GQLBatchedReqs a -> String
show :: GQLBatchedReqs a -> String
$cshowList :: forall a. Show a => [GQLBatchedReqs a] -> ShowS
showList :: [GQLBatchedReqs a] -> ShowS
Show, GQLBatchedReqs a -> GQLBatchedReqs a -> Bool
(GQLBatchedReqs a -> GQLBatchedReqs a -> Bool)
-> (GQLBatchedReqs a -> GQLBatchedReqs a -> Bool)
-> Eq (GQLBatchedReqs a)
forall a. Eq a => GQLBatchedReqs a -> GQLBatchedReqs a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => GQLBatchedReqs a -> GQLBatchedReqs a -> Bool
== :: GQLBatchedReqs a -> GQLBatchedReqs a -> Bool
$c/= :: forall a. Eq a => GQLBatchedReqs a -> GQLBatchedReqs a -> Bool
/= :: GQLBatchedReqs a -> GQLBatchedReqs a -> Bool
Eq, (forall x. GQLBatchedReqs a -> Rep (GQLBatchedReqs a) x)
-> (forall x. Rep (GQLBatchedReqs a) x -> GQLBatchedReqs a)
-> Generic (GQLBatchedReqs a)
forall x. Rep (GQLBatchedReqs a) x -> GQLBatchedReqs a
forall x. GQLBatchedReqs a -> Rep (GQLBatchedReqs a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (GQLBatchedReqs a) x -> GQLBatchedReqs a
forall a x. GQLBatchedReqs a -> Rep (GQLBatchedReqs a) x
$cfrom :: forall a x. GQLBatchedReqs a -> Rep (GQLBatchedReqs a) x
from :: forall x. GQLBatchedReqs a -> Rep (GQLBatchedReqs a) x
$cto :: forall a x. Rep (GQLBatchedReqs a) x -> GQLBatchedReqs a
to :: forall x. Rep (GQLBatchedReqs a) x -> GQLBatchedReqs a
Generic, (forall a b. (a -> b) -> GQLBatchedReqs a -> GQLBatchedReqs b)
-> (forall a b. a -> GQLBatchedReqs b -> GQLBatchedReqs a)
-> Functor GQLBatchedReqs
forall a b. a -> GQLBatchedReqs b -> GQLBatchedReqs a
forall a b. (a -> b) -> GQLBatchedReqs a -> GQLBatchedReqs 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) -> GQLBatchedReqs a -> GQLBatchedReqs b
fmap :: forall a b. (a -> b) -> GQLBatchedReqs a -> GQLBatchedReqs b
$c<$ :: forall a b. a -> GQLBatchedReqs b -> GQLBatchedReqs a
<$ :: forall a b. a -> GQLBatchedReqs b -> GQLBatchedReqs a
Functor)
instance (J.ToJSON a) => J.ToJSON (GQLBatchedReqs a) where
toJSON :: GQLBatchedReqs a -> Value
toJSON (GQLSingleRequest a
q) = a -> Value
forall a. ToJSON a => a -> Value
J.toJSON a
q
toJSON (GQLBatchedReqs [a]
qs) = [a] -> Value
forall a. ToJSON a => a -> Value
J.toJSON [a]
qs
instance (J.FromJSON a) => J.FromJSON (GQLBatchedReqs a) where
parseJSON :: Value -> Parser (GQLBatchedReqs a)
parseJSON arr :: Value
arr@J.Array {} = [a] -> GQLBatchedReqs a
forall a. [a] -> GQLBatchedReqs a
GQLBatchedReqs ([a] -> GQLBatchedReqs a)
-> Parser [a] -> Parser (GQLBatchedReqs a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [a]
forall a. FromJSON a => Value -> Parser a
J.parseJSON Value
arr
parseJSON Value
other = a -> GQLBatchedReqs a
forall a. a -> GQLBatchedReqs a
GQLSingleRequest (a -> GQLBatchedReqs a) -> Parser a -> Parser (GQLBatchedReqs a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser a
forall a. FromJSON a => Value -> Parser a
J.parseJSON Value
other
newtype GQLQueryText = GQLQueryText
{ GQLQueryText -> Text
_unGQLQueryText :: Text
}
deriving (Int -> GQLQueryText -> ShowS
[GQLQueryText] -> ShowS
GQLQueryText -> String
(Int -> GQLQueryText -> ShowS)
-> (GQLQueryText -> String)
-> ([GQLQueryText] -> ShowS)
-> Show GQLQueryText
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GQLQueryText -> ShowS
showsPrec :: Int -> GQLQueryText -> ShowS
$cshow :: GQLQueryText -> String
show :: GQLQueryText -> String
$cshowList :: [GQLQueryText] -> ShowS
showList :: [GQLQueryText] -> ShowS
Show, GQLQueryText -> GQLQueryText -> Bool
(GQLQueryText -> GQLQueryText -> Bool)
-> (GQLQueryText -> GQLQueryText -> Bool) -> Eq GQLQueryText
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GQLQueryText -> GQLQueryText -> Bool
== :: GQLQueryText -> GQLQueryText -> Bool
$c/= :: GQLQueryText -> GQLQueryText -> Bool
/= :: GQLQueryText -> GQLQueryText -> Bool
Eq, Eq GQLQueryText
Eq GQLQueryText
-> (GQLQueryText -> GQLQueryText -> Ordering)
-> (GQLQueryText -> GQLQueryText -> Bool)
-> (GQLQueryText -> GQLQueryText -> Bool)
-> (GQLQueryText -> GQLQueryText -> Bool)
-> (GQLQueryText -> GQLQueryText -> Bool)
-> (GQLQueryText -> GQLQueryText -> GQLQueryText)
-> (GQLQueryText -> GQLQueryText -> GQLQueryText)
-> Ord GQLQueryText
GQLQueryText -> GQLQueryText -> Bool
GQLQueryText -> GQLQueryText -> Ordering
GQLQueryText -> GQLQueryText -> GQLQueryText
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
$ccompare :: GQLQueryText -> GQLQueryText -> Ordering
compare :: GQLQueryText -> GQLQueryText -> Ordering
$c< :: GQLQueryText -> GQLQueryText -> Bool
< :: GQLQueryText -> GQLQueryText -> Bool
$c<= :: GQLQueryText -> GQLQueryText -> Bool
<= :: GQLQueryText -> GQLQueryText -> Bool
$c> :: GQLQueryText -> GQLQueryText -> Bool
> :: GQLQueryText -> GQLQueryText -> Bool
$c>= :: GQLQueryText -> GQLQueryText -> Bool
>= :: GQLQueryText -> GQLQueryText -> Bool
$cmax :: GQLQueryText -> GQLQueryText -> GQLQueryText
max :: GQLQueryText -> GQLQueryText -> GQLQueryText
$cmin :: GQLQueryText -> GQLQueryText -> GQLQueryText
min :: GQLQueryText -> GQLQueryText -> GQLQueryText
Ord, Eq GQLQueryText
Eq GQLQueryText
-> (Int -> GQLQueryText -> Int)
-> (GQLQueryText -> Int)
-> Hashable GQLQueryText
Int -> GQLQueryText -> Int
GQLQueryText -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> GQLQueryText -> Int
hashWithSalt :: Int -> GQLQueryText -> Int
$chash :: GQLQueryText -> Int
hash :: GQLQueryText -> Int
Hashable, String -> GQLQueryText
(String -> GQLQueryText) -> IsString GQLQueryText
forall a. (String -> a) -> IsString a
$cfromString :: String -> GQLQueryText
fromString :: String -> GQLQueryText
IsString)
deriving newtype (Value -> Parser [GQLQueryText]
Value -> Parser GQLQueryText
(Value -> Parser GQLQueryText)
-> (Value -> Parser [GQLQueryText]) -> FromJSON GQLQueryText
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser GQLQueryText
parseJSON :: Value -> Parser GQLQueryText
$cparseJSONList :: Value -> Parser [GQLQueryText]
parseJSONList :: Value -> Parser [GQLQueryText]
J.FromJSON, [GQLQueryText] -> Value
[GQLQueryText] -> Encoding
GQLQueryText -> Value
GQLQueryText -> Encoding
(GQLQueryText -> Value)
-> (GQLQueryText -> Encoding)
-> ([GQLQueryText] -> Value)
-> ([GQLQueryText] -> Encoding)
-> ToJSON GQLQueryText
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: GQLQueryText -> Value
toJSON :: GQLQueryText -> Value
$ctoEncoding :: GQLQueryText -> Encoding
toEncoding :: GQLQueryText -> Encoding
$ctoJSONList :: [GQLQueryText] -> Value
toJSONList :: [GQLQueryText] -> Value
$ctoEncodingList :: [GQLQueryText] -> Encoding
toEncodingList :: [GQLQueryText] -> Encoding
J.ToJSON)
type GQLReqUnparsed = GQLReq GQLQueryText
type GQLReqParsed = GQLReq GQLExecDoc
type ReqsText = GQLBatchedReqs (GQLReq GQLQueryText)
type GQLReqOutgoing = GQLReq SingleOperation
type SingleOperation = G.TypedOperationDefinition G.NoFragments G.Name
renderGQLReqOutgoing :: GQLReqOutgoing -> GQLReqUnparsed
renderGQLReqOutgoing :: GQLReqOutgoing -> GQLReqUnparsed
renderGQLReqOutgoing = (SingleOperation -> GQLQueryText)
-> GQLReqOutgoing -> GQLReqUnparsed
forall a b. (a -> b) -> GQLReq a -> GQLReq b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> GQLQueryText
GQLQueryText (Text -> GQLQueryText)
-> (SingleOperation -> Text) -> SingleOperation -> GQLQueryText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExecutableDocument Name -> Text
G.renderExecutableDoc (ExecutableDocument Name -> Text)
-> (SingleOperation -> ExecutableDocument Name)
-> SingleOperation
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TypedOperationDefinition FragmentSpread Name
-> ExecutableDocument Name
forall {var}.
TypedOperationDefinition FragmentSpread var
-> ExecutableDocument var
toExecDoc (TypedOperationDefinition FragmentSpread Name
-> ExecutableDocument Name)
-> (SingleOperation
-> TypedOperationDefinition FragmentSpread Name)
-> SingleOperation
-> ExecutableDocument Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SingleOperation -> TypedOperationDefinition FragmentSpread Name
forall var.
TypedOperationDefinition NoFragments var
-> TypedOperationDefinition FragmentSpread var
inlineFrags)
where
inlineFrags ::
G.TypedOperationDefinition G.NoFragments var ->
G.TypedOperationDefinition G.FragmentSpread var
inlineFrags :: forall var.
TypedOperationDefinition NoFragments var
-> TypedOperationDefinition FragmentSpread var
inlineFrags TypedOperationDefinition NoFragments var
opDef =
TypedOperationDefinition NoFragments var
opDef {_todSelectionSet :: SelectionSet FragmentSpread var
G._todSelectionSet = (NoFragments var -> FragmentSpread var)
-> SelectionSet NoFragments var -> SelectionSet FragmentSpread var
forall (frag :: * -> *) var (frag' :: * -> *).
(frag var -> frag' var)
-> SelectionSet frag var -> SelectionSet frag' var
G.fmapSelectionSetFragment NoFragments var -> FragmentSpread var
forall var. NoFragments var -> FragmentSpread var
G.inline (SelectionSet NoFragments var -> SelectionSet FragmentSpread var)
-> SelectionSet NoFragments var -> SelectionSet FragmentSpread var
forall a b. (a -> b) -> a -> b
$ TypedOperationDefinition NoFragments var
-> SelectionSet NoFragments var
forall (frag :: * -> *) var.
TypedOperationDefinition frag var -> SelectionSet frag var
G._todSelectionSet TypedOperationDefinition NoFragments var
opDef}
toExecDoc :: TypedOperationDefinition FragmentSpread var
-> ExecutableDocument var
toExecDoc =
[ExecutableDefinition var] -> ExecutableDocument var
forall var. [ExecutableDefinition var] -> ExecutableDocument var
G.ExecutableDocument ([ExecutableDefinition var] -> ExecutableDocument var)
-> (TypedOperationDefinition FragmentSpread var
-> [ExecutableDefinition var])
-> TypedOperationDefinition FragmentSpread var
-> ExecutableDocument var
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExecutableDefinition var -> [ExecutableDefinition var]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ExecutableDefinition var -> [ExecutableDefinition var])
-> (TypedOperationDefinition FragmentSpread var
-> ExecutableDefinition var)
-> TypedOperationDefinition FragmentSpread var
-> [ExecutableDefinition var]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OperationDefinition FragmentSpread var -> ExecutableDefinition var
forall var.
OperationDefinition FragmentSpread var -> ExecutableDefinition var
G.ExecutableDefinitionOperation (OperationDefinition FragmentSpread var
-> ExecutableDefinition var)
-> (TypedOperationDefinition FragmentSpread var
-> OperationDefinition FragmentSpread var)
-> TypedOperationDefinition FragmentSpread var
-> ExecutableDefinition var
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TypedOperationDefinition FragmentSpread var
-> OperationDefinition FragmentSpread var
forall (frag :: * -> *) var.
TypedOperationDefinition frag var -> OperationDefinition frag var
G.OperationDefinitionTyped
{-# INLINEABLE getSingleOperation #-}
getSingleOperation ::
(MonadError QErr m) =>
GQLReqParsed ->
m SingleOperation
getSingleOperation :: forall (m :: * -> *).
MonadError QErr m =>
GQLReqParsed -> m SingleOperation
getSingleOperation (GQLReq Maybe OperationName
opNameM GQLExecDoc
q Maybe VariableValues
_varValsM) = do
let ([SelectionSet FragmentSpread Name]
selSets, [TypedOperationDefinition FragmentSpread Name]
opDefs, [FragmentDefinition]
fragments) = [ExecutableDefinition Name]
-> ([SelectionSet FragmentSpread Name],
[TypedOperationDefinition FragmentSpread Name],
[FragmentDefinition])
forall var.
[ExecutableDefinition var]
-> ([SelectionSet FragmentSpread var],
[TypedOperationDefinition FragmentSpread var],
[FragmentDefinition])
G.partitionExDefs ([ExecutableDefinition Name]
-> ([SelectionSet FragmentSpread Name],
[TypedOperationDefinition FragmentSpread Name],
[FragmentDefinition]))
-> [ExecutableDefinition Name]
-> ([SelectionSet FragmentSpread Name],
[TypedOperationDefinition FragmentSpread Name],
[FragmentDefinition])
forall a b. (a -> b) -> a -> b
$ GQLExecDoc -> [ExecutableDefinition Name]
unGQLExecDoc GQLExecDoc
q
G.TypedOperationDefinition {[Directive Name]
SelectionSet FragmentSpread Name
[VariableDefinition]
Maybe Name
OperationType
_todSelectionSet :: forall (frag :: * -> *) var.
TypedOperationDefinition frag var -> SelectionSet frag var
_todType :: OperationType
_todName :: Maybe Name
_todVariableDefinitions :: [VariableDefinition]
_todDirectives :: [Directive Name]
_todSelectionSet :: SelectionSet FragmentSpread Name
_todType :: forall (frag :: * -> *) var.
TypedOperationDefinition frag var -> OperationType
_todName :: forall (frag :: * -> *) var.
TypedOperationDefinition frag var -> Maybe Name
_todVariableDefinitions :: forall (frag :: * -> *) var.
TypedOperationDefinition frag var -> [VariableDefinition]
_todDirectives :: forall (frag :: * -> *) var.
TypedOperationDefinition frag var -> [Directive var]
..} <-
case (Maybe OperationName
opNameM, [SelectionSet FragmentSpread Name]
selSets, [TypedOperationDefinition FragmentSpread Name]
opDefs) of
(Just OperationName
opName, [], [TypedOperationDefinition FragmentSpread Name]
_) -> do
let n :: Name
n = OperationName -> Name
_unOperationName OperationName
opName
opDefM :: Maybe (TypedOperationDefinition FragmentSpread Name)
opDefM = (TypedOperationDefinition FragmentSpread Name -> Bool)
-> [TypedOperationDefinition FragmentSpread Name]
-> Maybe (TypedOperationDefinition FragmentSpread Name)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\TypedOperationDefinition FragmentSpread Name
opDef -> TypedOperationDefinition FragmentSpread Name -> Maybe Name
forall (frag :: * -> *) var.
TypedOperationDefinition frag var -> Maybe Name
G._todName TypedOperationDefinition FragmentSpread Name
opDef Maybe Name -> Maybe Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name -> Maybe Name
forall a. a -> Maybe a
Just Name
n) [TypedOperationDefinition FragmentSpread Name]
opDefs
Maybe (TypedOperationDefinition FragmentSpread Name)
-> m (TypedOperationDefinition FragmentSpread Name)
-> m (TypedOperationDefinition FragmentSpread Name)
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
onNothing Maybe (TypedOperationDefinition FragmentSpread Name)
opDefM
(m (TypedOperationDefinition FragmentSpread Name)
-> m (TypedOperationDefinition FragmentSpread Name))
-> m (TypedOperationDefinition FragmentSpread Name)
-> m (TypedOperationDefinition FragmentSpread Name)
forall a b. (a -> b) -> a -> b
$ Code -> Text -> m (TypedOperationDefinition FragmentSpread Name)
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
ValidationFailed
(Text -> m (TypedOperationDefinition FragmentSpread Name))
-> Text -> m (TypedOperationDefinition FragmentSpread Name)
forall a b. (a -> b) -> a -> b
$ Text
"no such operation found in the document: "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Name -> Text
forall t. ToTxt t => t -> Text
dquote Name
n
(Just OperationName
_, [SelectionSet FragmentSpread Name]
_, [TypedOperationDefinition FragmentSpread Name]
_) ->
Code -> Text -> m (TypedOperationDefinition FragmentSpread Name)
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
ValidationFailed
(Text -> m (TypedOperationDefinition FragmentSpread Name))
-> Text -> m (TypedOperationDefinition FragmentSpread Name)
forall a b. (a -> b) -> a -> b
$ Text
"operationName cannot be used when "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"an anonymous operation exists in the document"
(Maybe OperationName
Nothing, [SelectionSet FragmentSpread Name
selSet], []) ->
TypedOperationDefinition FragmentSpread Name
-> m (TypedOperationDefinition FragmentSpread Name)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (TypedOperationDefinition FragmentSpread Name
-> m (TypedOperationDefinition FragmentSpread Name))
-> TypedOperationDefinition FragmentSpread Name
-> m (TypedOperationDefinition FragmentSpread Name)
forall a b. (a -> b) -> a -> b
$ OperationType
-> Maybe Name
-> [VariableDefinition]
-> [Directive Name]
-> SelectionSet FragmentSpread Name
-> TypedOperationDefinition FragmentSpread Name
forall (frag :: * -> *) var.
OperationType
-> Maybe Name
-> [VariableDefinition]
-> [Directive var]
-> SelectionSet frag var
-> TypedOperationDefinition frag var
G.TypedOperationDefinition OperationType
G.OperationTypeQuery Maybe Name
forall a. Maybe a
Nothing [] [] SelectionSet FragmentSpread Name
selSet
(Maybe OperationName
Nothing, [], [TypedOperationDefinition FragmentSpread Name
opDef]) ->
TypedOperationDefinition FragmentSpread Name
-> m (TypedOperationDefinition FragmentSpread Name)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return TypedOperationDefinition FragmentSpread Name
opDef
(Maybe OperationName
Nothing, [SelectionSet FragmentSpread Name]
_, [TypedOperationDefinition FragmentSpread Name]
_) ->
Code -> Text -> m (TypedOperationDefinition FragmentSpread Name)
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
ValidationFailed
(Text -> m (TypedOperationDefinition FragmentSpread Name))
-> Text -> m (TypedOperationDefinition FragmentSpread Name)
forall a b. (a -> b) -> a -> b
$ Text
"exactly one operation has to be present "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"in the document when operationName is not specified"
SelectionSet NoFragments Name
inlinedSelSet <- [FragmentDefinition]
-> SelectionSet FragmentSpread Name
-> m (SelectionSet NoFragments Name)
forall (m :: * -> *) (t :: * -> *).
(MonadError QErr m, Foldable t) =>
t FragmentDefinition
-> SelectionSet FragmentSpread Name
-> m (SelectionSet NoFragments Name)
EI.inlineSelectionSet [FragmentDefinition]
fragments SelectionSet FragmentSpread Name
_todSelectionSet
SingleOperation -> m SingleOperation
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SingleOperation -> m SingleOperation)
-> SingleOperation -> m SingleOperation
forall a b. (a -> b) -> a -> b
$ G.TypedOperationDefinition {_todSelectionSet :: SelectionSet NoFragments Name
_todSelectionSet = SelectionSet NoFragments Name
inlinedSelSet, [Directive Name]
[VariableDefinition]
Maybe Name
OperationType
_todType :: OperationType
_todName :: Maybe Name
_todVariableDefinitions :: [VariableDefinition]
_todDirectives :: [Directive Name]
_todType :: OperationType
_todName :: Maybe Name
_todVariableDefinitions :: [VariableDefinition]
_todDirectives :: [Directive Name]
..}
toParsed :: (MonadError QErr m) => GQLReqUnparsed -> m GQLReqParsed
toParsed :: forall (m :: * -> *).
MonadError QErr m =>
GQLReqUnparsed -> m GQLReqParsed
toParsed GQLReqUnparsed
req = case Text -> Either Text (ExecutableDocument Name)
G.parseExecutableDoc Text
gqlText of
Left Text
_ -> Text -> m GQLReqParsed -> m GQLReqParsed
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"query" (m GQLReqParsed -> m GQLReqParsed)
-> m GQLReqParsed -> m GQLReqParsed
forall a b. (a -> b) -> a -> b
$ Code -> Text -> m GQLReqParsed
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
ValidationFailed Text
"not a valid graphql query"
Right ExecutableDocument Name
a -> GQLReqParsed -> m GQLReqParsed
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (GQLReqParsed -> m GQLReqParsed) -> GQLReqParsed -> m GQLReqParsed
forall a b. (a -> b) -> a -> b
$ GQLReqUnparsed
req {_grQuery :: GQLExecDoc
_grQuery = [ExecutableDefinition Name] -> GQLExecDoc
GQLExecDoc ([ExecutableDefinition Name] -> GQLExecDoc)
-> [ExecutableDefinition Name] -> GQLExecDoc
forall a b. (a -> b) -> a -> b
$ ExecutableDocument Name -> [ExecutableDefinition Name]
forall var. ExecutableDocument var -> [ExecutableDefinition var]
G.getExecutableDefinitions ExecutableDocument Name
a}
where
gqlText :: Text
gqlText = GQLQueryText -> Text
_unGQLQueryText (GQLQueryText -> Text) -> GQLQueryText -> Text
forall a b. (a -> b) -> a -> b
$ GQLReqUnparsed -> GQLQueryText
forall a. GQLReq a -> a
_grQuery GQLReqUnparsed
req
getOpNameFromParsedReq :: GQLReqParsed -> Maybe OperationName
getOpNameFromParsedReq :: GQLReqParsed -> Maybe OperationName
getOpNameFromParsedReq GQLReqParsed
reqParsed =
case [ExecutableDefinition Name]
execDefs of
[G.ExecutableDefinitionOperation (G.OperationDefinitionTyped (G.TypedOperationDefinition OperationType
_ Maybe Name
maybeName [VariableDefinition]
_ [Directive Name]
_ SelectionSet FragmentSpread Name
_))] ->
let maybeOpNameFromRequestBody :: Maybe OperationName
maybeOpNameFromRequestBody = GQLReqParsed -> Maybe OperationName
forall a. GQLReq a -> Maybe OperationName
_grOperationName GQLReqParsed
reqParsed
maybeOpNameFromFirstExecDef :: Maybe OperationName
maybeOpNameFromFirstExecDef = Name -> OperationName
OperationName (Name -> OperationName) -> Maybe Name -> Maybe OperationName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Name
maybeName
in Maybe OperationName
maybeOpNameFromRequestBody Maybe OperationName -> Maybe OperationName -> Maybe OperationName
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe OperationName
maybeOpNameFromFirstExecDef
[ExecutableDefinition Name]
_ -> GQLReqParsed -> Maybe OperationName
forall a. GQLReq a -> Maybe OperationName
_grOperationName GQLReqParsed
reqParsed
where
execDefs :: [ExecutableDefinition Name]
execDefs = GQLExecDoc -> [ExecutableDefinition Name]
unGQLExecDoc (GQLExecDoc -> [ExecutableDefinition Name])
-> GQLExecDoc -> [ExecutableDefinition Name]
forall a b. (a -> b) -> a -> b
$ GQLReqParsed -> GQLExecDoc
forall a. GQLReq a -> a
_grQuery GQLReqParsed
reqParsed
encodeGQErr :: Bool -> QErr -> J.Encoding
encodeGQErr :: Bool -> QErr -> Encoding
encodeGQErr Bool
includeInternal QErr
qErr =
Series -> Encoding
J.pairs (Key -> Encoding -> Series
J.pair Key
"errors" (Encoding -> Series) -> Encoding -> Series
forall a b. (a -> b) -> a -> b
$ (Encoding -> Encoding) -> [Encoding] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
J.list Encoding -> Encoding
forall a. a -> a
id [Bool -> QErr -> Encoding
encodeGQLErr Bool
includeInternal QErr
qErr])
type GQResult a = Either GQExecError a
newtype GQExecError = GQExecError [J.Encoding]
deriving (Int -> GQExecError -> ShowS
[GQExecError] -> ShowS
GQExecError -> String
(Int -> GQExecError -> ShowS)
-> (GQExecError -> String)
-> ([GQExecError] -> ShowS)
-> Show GQExecError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GQExecError -> ShowS
showsPrec :: Int -> GQExecError -> ShowS
$cshow :: GQExecError -> String
show :: GQExecError -> String
$cshowList :: [GQExecError] -> ShowS
showList :: [GQExecError] -> ShowS
Show, GQExecError -> GQExecError -> Bool
(GQExecError -> GQExecError -> Bool)
-> (GQExecError -> GQExecError -> Bool) -> Eq GQExecError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GQExecError -> GQExecError -> Bool
== :: GQExecError -> GQExecError -> Bool
$c/= :: GQExecError -> GQExecError -> Bool
/= :: GQExecError -> GQExecError -> Bool
Eq)
type GQResponse = GQResult BL.ByteString
isExecError :: GQResult a -> Bool
isExecError :: forall a. GQResult a -> Bool
isExecError = Either GQExecError a -> Bool
forall a b. Either a b -> Bool
isLeft
encodeGQExecError :: GQExecError -> J.Encoding
encodeGQExecError :: GQExecError -> Encoding
encodeGQExecError (GQExecError [Encoding]
errs) = (Encoding -> Encoding) -> [Encoding] -> Encoding
forall a. (a -> Encoding) -> [a] -> Encoding
J.list Encoding -> Encoding
forall a. a -> a
id [Encoding]
errs
encodeGQResp :: GQResponse -> EncJSON
encodeGQResp :: GQResponse -> EncJSON
encodeGQResp GQResponse
gqResp =
[(Text, EncJSON)] -> EncJSON
encJFromAssocList ([(Text, EncJSON)] -> EncJSON) -> [(Text, EncJSON)] -> EncJSON
forall a b. (a -> b) -> a -> b
$ case GQResponse
gqResp of
Right ByteString
r -> [(Text
"data", ByteString -> EncJSON
encJFromLbsWithoutSoh ByteString
r)]
Left GQExecError
e -> [(Text
"data", Builder -> EncJSON
encJFromBuilder Builder
"null"), (Text
"errors", Encoding -> EncJSON
encJFromJEncoding (Encoding -> EncJSON) -> Encoding -> EncJSON
forall a b. (a -> b) -> a -> b
$ GQExecError -> Encoding
encodeGQExecError GQExecError
e)]
decodeGQResp :: EncJSON -> (Maybe GQResponse, EncJSON)
decodeGQResp :: EncJSON -> (Maybe GQResponse, EncJSON)
decodeGQResp EncJSON
encJson =
let gqResp :: Maybe GQResponse
gqResp =
case forall a. FromJSON a => ByteString -> Maybe a
J.decode @J.Value (EncJSON -> ByteString
encJToLBS EncJSON
encJson) of
Just (J.Object Object
v) ->
case Key -> Object -> Maybe Value
forall v. Key -> KeyMap v -> Maybe v
KM.lookup Key
"error" Object
v of
Just Value
err -> GQResponse -> Maybe GQResponse
forall a. a -> Maybe a
Just (ByteString -> GQResponse
forall a b. b -> Either a b
Right (ByteString -> GQResponse) -> ByteString -> GQResponse
forall a b. (a -> b) -> a -> b
$ Value -> ByteString
forall a. ToJSON a => a -> ByteString
J.encode Value
err)
Maybe Value
Nothing -> ByteString -> GQResponse
forall a b. b -> Either a b
Right (ByteString -> GQResponse)
-> (Value -> ByteString) -> Value -> GQResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> ByteString
forall a. ToJSON a => a -> ByteString
J.encode (Value -> GQResponse) -> Maybe Value -> Maybe GQResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> Object -> Maybe Value
forall v. Key -> KeyMap v -> Maybe v
KM.lookup Key
"data" Object
v
Maybe Value
_ -> Maybe GQResponse
forall a. Maybe a
Nothing
in (Maybe GQResponse
gqResp, EncJSON
encJson)
encodeHTTPResp :: GQResponse -> EncJSON
encodeHTTPResp :: GQResponse -> EncJSON
encodeHTTPResp = \case
Right ByteString
r -> ByteString -> EncJSON
encJFromLBS ByteString
r
Left GQExecError
e -> Encoding -> EncJSON
encJFromJEncoding (Encoding -> EncJSON) -> Encoding -> EncJSON
forall a b. (a -> b) -> a -> b
$ GQExecError -> Encoding
encodeGQExecError GQExecError
e