{-# language DataKinds #-}
{-# language FlexibleContexts #-}
{-# language GADTs #-}
{-# language OverloadedLists #-}
{-# language OverloadedStrings #-}
{-# language RankNTypes #-}
{-# language ScopedTypeVariables #-}
{-# language TypeApplications #-}
module Mu.GraphQL.Server (
GraphQLApp
, runGraphQLApp
, runGraphQLAppSettings
, runGraphQLAppQuery
, runGraphQLAppTrans
, graphQLApp
, graphQLAppQuery
, graphQLAppTrans
, graphQLAppTransQuery
, liftServerConduit
) where
import Control.Applicative ((<|>))
import Control.Exception (throw)
import Control.Monad.Except (MonadIO (..), join, runExceptT)
import qualified Data.Aeson as A
import Data.Aeson.Text (encodeToLazyText)
import Data.ByteString.Char8 (split)
import Data.ByteString.Lazy (fromStrict, toStrict)
import Data.Conduit (ConduitT, transPipe)
import qualified Data.HashMap.Strict as HM
import Data.Proxy (Proxy (..))
import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8')
import Data.Text.Encoding.Error (UnicodeException (..))
import qualified Data.Text.Lazy.Encoding as T
import qualified Language.GraphQL.AST as GQL
import Network.HTTP.Types.Header (hContentType)
import Network.HTTP.Types.Method (StdMethod (..), parseMethod)
import Network.HTTP.Types.Status (ok200)
import Network.Wai
import Network.Wai.Handler.Warp (Port, Settings, run, runSettings)
import qualified Network.Wai.Handler.WebSockets as WS
import qualified Network.WebSockets as WS
import Mu.GraphQL.Quasi.LostParser (parseDoc)
import Mu.GraphQL.Query.Parse (VariableMapC)
import Mu.GraphQL.Query.Run (GraphQLApp, runPipeline, runSubscriptionPipeline)
import Mu.GraphQL.Subscription.Protocol (protocol)
import Mu.Server (ServerErrorIO, ServerT)
data GraphQLInput = GraphQLInput T.Text VariableMapC (Maybe T.Text)
instance A.FromJSON GraphQLInput where
parseJSON :: Value -> Parser GraphQLInput
parseJSON = String
-> (Object -> Parser GraphQLInput) -> Value -> Parser GraphQLInput
forall a. String -> (Object -> Parser a) -> Value -> Parser a
A.withObject String
"GraphQLInput" ((Object -> Parser GraphQLInput) -> Value -> Parser GraphQLInput)
-> (Object -> Parser GraphQLInput) -> Value -> Parser GraphQLInput
forall a b. (a -> b) -> a -> b
$
\Object
v -> Text -> VariableMapC -> Maybe Text -> GraphQLInput
GraphQLInput
(Text -> VariableMapC -> Maybe Text -> GraphQLInput)
-> Parser Text
-> Parser (VariableMapC -> Maybe Text -> GraphQLInput)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
A..: Text
"query"
Parser (VariableMapC -> Maybe Text -> GraphQLInput)
-> Parser VariableMapC -> Parser (Maybe Text -> GraphQLInput)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
v Object -> Text -> Parser VariableMapC
forall a. FromJSON a => Object -> Text -> Parser a
A..: Text
"variables" Parser VariableMapC -> Parser VariableMapC -> Parser VariableMapC
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> VariableMapC -> Parser VariableMapC
forall (f :: * -> *) a. Applicative f => a -> f a
pure VariableMapC
forall k v. HashMap k v
HM.empty)
Parser (Maybe Text -> GraphQLInput)
-> Parser (Maybe Text) -> Parser GraphQLInput
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
A..:? Text
"operationName"
graphQLApp ::
( GraphQLApp p qr mut sub ServerErrorIO chn hs )
=> ServerT chn GQL.Field p ServerErrorIO hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> Application
graphQLApp :: ServerT chn Field p ServerErrorIO hs
-> Proxy qr -> Proxy mut -> Proxy sub -> Application
graphQLApp = (forall a. ServerErrorIO a -> ServerErrorIO a)
-> ServerT chn Field p ServerErrorIO hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> Application
forall (p :: Package') (qr :: Maybe Symbol) (mut :: Maybe Symbol)
(sub :: Maybe Symbol) (m :: * -> *) (chn :: ServiceChain Symbol)
(hs :: [[*]]).
GraphQLApp p qr mut sub m chn hs =>
(forall a. m a -> ServerErrorIO a)
-> ServerT chn Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> Application
graphQLAppTrans forall a. a -> a
forall a. ServerErrorIO a -> ServerErrorIO a
id
graphQLAppQuery ::
forall qr p chn hs.
( GraphQLApp p ('Just qr) 'Nothing 'Nothing ServerErrorIO chn hs )
=> ServerT chn GQL.Field p ServerErrorIO hs
-> Proxy qr
-> Application
graphQLAppQuery :: ServerT chn Field p ServerErrorIO hs -> Proxy qr -> Application
graphQLAppQuery ServerT chn Field p ServerErrorIO hs
svr Proxy qr
_
= ServerT chn Field p ServerErrorIO hs
-> Proxy ('Just qr)
-> Proxy 'Nothing
-> Proxy 'Nothing
-> Application
forall (p :: Package') (qr :: Maybe Symbol) (mut :: Maybe Symbol)
(sub :: Maybe Symbol) (chn :: ServiceChain Symbol) (hs :: [[*]]).
GraphQLApp p qr mut sub ServerErrorIO chn hs =>
ServerT chn Field p ServerErrorIO hs
-> Proxy qr -> Proxy mut -> Proxy sub -> Application
graphQLApp ServerT chn Field p ServerErrorIO hs
svr (Proxy ('Just qr)
forall k (t :: k). Proxy t
Proxy @('Just qr)) (Proxy 'Nothing
forall k (t :: k). Proxy t
Proxy @'Nothing) (Proxy 'Nothing
forall k (t :: k). Proxy t
Proxy @'Nothing)
graphQLAppTransQuery ::
forall qr m p chn hs.
( GraphQLApp p ('Just qr) 'Nothing 'Nothing m chn hs )
=> (forall a. m a -> ServerErrorIO a)
-> ServerT chn GQL.Field p m hs
-> Proxy qr
-> Application
graphQLAppTransQuery :: (forall a. m a -> ServerErrorIO a)
-> ServerT chn Field p m hs -> Proxy qr -> Application
graphQLAppTransQuery forall a. m a -> ServerErrorIO a
f ServerT chn Field p m hs
svr Proxy qr
_
= (forall a. m a -> ServerErrorIO a)
-> ServerT chn Field p m hs
-> Proxy ('Just qr)
-> Proxy 'Nothing
-> Proxy 'Nothing
-> Application
forall (p :: Package') (qr :: Maybe Symbol) (mut :: Maybe Symbol)
(sub :: Maybe Symbol) (m :: * -> *) (chn :: ServiceChain Symbol)
(hs :: [[*]]).
GraphQLApp p qr mut sub m chn hs =>
(forall a. m a -> ServerErrorIO a)
-> ServerT chn Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> Application
graphQLAppTrans forall a. m a -> ServerErrorIO a
f ServerT chn Field p m hs
svr (Proxy ('Just qr)
forall k (t :: k). Proxy t
Proxy @('Just qr)) (Proxy 'Nothing
forall k (t :: k). Proxy t
Proxy @'Nothing) (Proxy 'Nothing
forall k (t :: k). Proxy t
Proxy @'Nothing)
graphQLAppTrans ::
( GraphQLApp p qr mut sub m chn hs )
=> (forall a. m a -> ServerErrorIO a)
-> ServerT chn GQL.Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> Application
graphQLAppTrans :: (forall a. m a -> ServerErrorIO a)
-> ServerT chn Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> Application
graphQLAppTrans forall a. m a -> ServerErrorIO a
f ServerT chn Field p m hs
server Proxy qr
q Proxy mut
m Proxy sub
s
= ConnectionOptions -> ServerApp -> Application -> Application
WS.websocketsOr ConnectionOptions
WS.defaultConnectionOptions
((forall a. m a -> ServerErrorIO a)
-> ServerT chn Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> ServerApp
forall (p :: Package') (qr :: Maybe Symbol) (mut :: Maybe Symbol)
(sub :: Maybe Symbol) (m :: * -> *) (chn :: ServiceChain Symbol)
(hs :: [[*]]).
GraphQLApp p qr mut sub m chn hs =>
(forall a. m a -> ServerErrorIO a)
-> ServerT chn Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> ServerApp
wsGraphQLAppTrans forall a. m a -> ServerErrorIO a
f ServerT chn Field p m hs
server Proxy qr
q Proxy mut
m Proxy sub
s)
((forall a. m a -> ServerErrorIO a)
-> ServerT chn Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> Application
forall (p :: Package') (qr :: Maybe Symbol) (mut :: Maybe Symbol)
(sub :: Maybe Symbol) (m :: * -> *) (chn :: ServiceChain Symbol)
(hs :: [[*]]).
GraphQLApp p qr mut sub m chn hs =>
(forall a. m a -> ServerErrorIO a)
-> ServerT chn Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> Application
httpGraphQLAppTrans forall a. m a -> ServerErrorIO a
f ServerT chn Field p m hs
server Proxy qr
q Proxy mut
m Proxy sub
s)
httpGraphQLAppTrans ::
( GraphQLApp p qr mut sub m chn hs )
=> (forall a. m a -> ServerErrorIO a)
-> ServerT chn GQL.Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> Application
httpGraphQLAppTrans :: (forall a. m a -> ServerErrorIO a)
-> ServerT chn Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> Application
httpGraphQLAppTrans forall a. m a -> ServerErrorIO a
f ServerT chn Field p m hs
server Proxy qr
q Proxy mut
m Proxy sub
s Request
req Response -> IO ResponseReceived
res =
case Method -> Either Method StdMethod
parseMethod (Request -> Method
requestMethod Request
req) of
Left Method
err -> Text -> IO ResponseReceived
toError (Text -> IO ResponseReceived) -> Text -> IO ResponseReceived
forall a b. (a -> b) -> a -> b
$ (UnicodeException -> Text)
-> (Text -> Text) -> Either UnicodeException Text -> Text
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either UnicodeException -> Text
unpackUnicodeException Text -> Text
forall a. a -> a
id (Method -> Either UnicodeException Text
decodeUtf8' Method
err)
Right StdMethod
GET -> do
let qst :: Query
qst = Request -> Query
queryString Request
req
opN :: Maybe (Either UnicodeException Text)
opN = Method -> Either UnicodeException Text
decodeUtf8' (Method -> Either UnicodeException Text)
-> Maybe Method -> Maybe (Either UnicodeException Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Maybe Method) -> Maybe Method
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Method -> Query -> Maybe (Maybe Method)
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Method
"operationName" Query
qst)
decodedQuery :: Maybe (Either UnicodeException Text)
decodedQuery = (Method -> Either UnicodeException Text)
-> Maybe Method -> Maybe (Either UnicodeException Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Method -> Either UnicodeException Text
decodeUtf8' (Maybe Method -> Maybe (Either UnicodeException Text))
-> Maybe (Maybe Method) -> Maybe (Either UnicodeException Text)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Method -> Query -> Maybe (Maybe Method)
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Method
"query" Query
qst
case (Maybe (Either UnicodeException Text)
decodedQuery, Method -> Query -> Maybe (Maybe Method)
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Method
"variables" Query
qst) of
(Just (Right Text
qry), Just (Just Method
vars)) ->
case ByteString -> Either String VariableMapC
forall a. FromJSON a => ByteString -> Either String a
A.eitherDecode (ByteString -> Either String VariableMapC)
-> ByteString -> Either String VariableMapC
forall a b. (a -> b) -> a -> b
$ Method -> ByteString
fromStrict Method
vars of
Left String
err -> Text -> IO ResponseReceived
toError (Text -> IO ResponseReceived) -> Text -> IO ResponseReceived
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
err
Right VariableMapC
vrs -> case Maybe (Either UnicodeException Text)
-> Either UnicodeException (Maybe Text)
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence Maybe (Either UnicodeException Text)
opN of
Left UnicodeException
err -> Text -> IO ResponseReceived
toError (Text -> IO ResponseReceived) -> Text -> IO ResponseReceived
forall a b. (a -> b) -> a -> b
$ Text
"Could not parse operation name: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> UnicodeException -> Text
unpackUnicodeException UnicodeException
err
Right Maybe Text
opName -> Maybe Text -> VariableMapC -> Text -> IO ResponseReceived
execQuery Maybe Text
opName VariableMapC
vrs Text
qry
(Just (Right Text
qry), Maybe (Maybe Method)
_) -> case Maybe (Either UnicodeException Text)
-> Either UnicodeException (Maybe Text)
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence Maybe (Either UnicodeException Text)
opN of
Left UnicodeException
err -> Text -> IO ResponseReceived
toError (Text -> IO ResponseReceived) -> Text -> IO ResponseReceived
forall a b. (a -> b) -> a -> b
$ Text
"Could not parse query: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> UnicodeException -> Text
unpackUnicodeException UnicodeException
err
Right Maybe Text
opName -> Maybe Text -> VariableMapC -> Text -> IO ResponseReceived
execQuery Maybe Text
opName VariableMapC
forall k v. HashMap k v
HM.empty Text
qry
(Maybe (Either UnicodeException Text), Maybe (Maybe Method))
_ -> Text -> IO ResponseReceived
toError Text
"Error parsing query"
Right StdMethod
POST -> do
ByteString
body <- Request -> IO ByteString
strictRequestBody Request
req
case Char -> Method -> [Method]
split Char
';' (Method -> [Method]) -> Maybe Method -> Maybe [Method]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HeaderName -> [(HeaderName, Method)] -> Maybe Method
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup HeaderName
hContentType (Request -> [(HeaderName, Method)]
requestHeaders Request
req) of
Just (Method
"application/json" : [Method]
_) ->
case ByteString -> Either String GraphQLInput
forall a. FromJSON a => ByteString -> Either String a
A.eitherDecode ByteString
body of
Left String
err -> Text -> IO ResponseReceived
toError (Text -> IO ResponseReceived) -> Text -> IO ResponseReceived
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
err
Right (GraphQLInput Text
qry VariableMapC
vars Maybe Text
opName) -> Maybe Text -> VariableMapC -> Text -> IO ResponseReceived
execQuery Maybe Text
opName VariableMapC
vars Text
qry
Just (Method
"application/graphql" : [Method]
_) ->
case Method -> Either UnicodeException Text
decodeUtf8' (Method -> Either UnicodeException Text)
-> Method -> Either UnicodeException Text
forall a b. (a -> b) -> a -> b
$ ByteString -> Method
toStrict ByteString
body of
Left UnicodeException
err -> Text -> IO ResponseReceived
toError (Text -> IO ResponseReceived) -> Text -> IO ResponseReceived
forall a b. (a -> b) -> a -> b
$ Text
"Could not decode utf8 from body: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> UnicodeException -> Text
unpackUnicodeException UnicodeException
err
Right Text
msg -> Maybe Text -> VariableMapC -> Text -> IO ResponseReceived
execQuery Maybe Text
forall a. Maybe a
Nothing VariableMapC
forall k v. HashMap k v
HM.empty Text
msg
Maybe [Method]
_ -> Text -> IO ResponseReceived
toError Text
"No `Content-Type` header found!"
Either Method StdMethod
_ -> Text -> IO ResponseReceived
toError Text
"Unsupported method"
where
execQuery :: Maybe T.Text -> VariableMapC -> T.Text -> IO ResponseReceived
execQuery :: Maybe Text -> VariableMapC -> Text -> IO ResponseReceived
execQuery Maybe Text
opn VariableMapC
vals Text
qry =
case Text -> Either Text [Definition]
parseDoc Text
qry of
Left Text
err -> Text -> IO ResponseReceived
toError Text
err
Right [Definition]
doc -> (forall a. m a -> ServerErrorIO a)
-> [(HeaderName, Method)]
-> ServerT chn Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> Maybe Text
-> VariableMapC
-> [Definition]
-> IO Value
forall (qr :: Maybe Symbol) (mut :: Maybe Symbol)
(sub :: Maybe Symbol) (p :: Package') (m :: * -> *)
(chn :: ServiceChain Symbol) (hs :: [[*]]).
GraphQLApp p qr mut sub m chn hs =>
(forall a. m a -> ServerErrorIO a)
-> [(HeaderName, Method)]
-> ServerT chn Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> Maybe Text
-> VariableMapC
-> [Definition]
-> IO Value
runPipeline forall a. m a -> ServerErrorIO a
f (Request -> [(HeaderName, Method)]
requestHeaders Request
req) ServerT chn Field p m hs
server Proxy qr
q Proxy mut
m Proxy sub
s Maybe Text
opn VariableMapC
vals [Definition]
doc
IO Value -> (Value -> IO ResponseReceived) -> IO ResponseReceived
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Value -> IO ResponseReceived
toResponse
toError :: T.Text -> IO ResponseReceived
toError :: Text -> IO ResponseReceived
toError Text
err = Value -> IO ResponseReceived
toResponse (Value -> IO ResponseReceived) -> Value -> IO ResponseReceived
forall a b. (a -> b) -> a -> b
$ [Pair] -> Value
A.object [ (Text
"errors", Array -> Value
A.Array [ [Pair] -> Value
A.object [ (Text
"message", Text -> Value
A.String Text
err) ] ])]
toResponse :: A.Value -> IO ResponseReceived
toResponse :: Value -> IO ResponseReceived
toResponse = Response -> IO ResponseReceived
res (Response -> IO ResponseReceived)
-> (Value -> Response) -> Value -> IO ResponseReceived
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Status -> [(HeaderName, Method)] -> Builder -> Response
responseBuilder Status
ok200 [] (Builder -> Response) -> (Value -> Builder) -> Value -> Response
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Builder
T.encodeUtf8Builder (Text -> Builder) -> (Value -> Text) -> Value -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText
unpackUnicodeException :: UnicodeException -> T.Text
unpackUnicodeException :: UnicodeException -> Text
unpackUnicodeException (DecodeError String
str Maybe Word8
_) = String -> Text
T.pack String
str
unpackUnicodeException UnicodeException
_ = String -> Text
forall a. HasCallStack => String -> a
error String
"EncodeError is deprecated"
wsGraphQLAppTrans
:: ( GraphQLApp p qr mut sub m chn hs )
=> (forall a. m a -> ServerErrorIO a)
-> ServerT chn GQL.Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> WS.ServerApp
wsGraphQLAppTrans :: (forall a. m a -> ServerErrorIO a)
-> ServerT chn Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> ServerApp
wsGraphQLAppTrans forall a. m a -> ServerErrorIO a
f ServerT chn Field p m hs
server Proxy qr
q Proxy mut
m Proxy sub
s PendingConnection
conn
= do let headers :: [(HeaderName, Method)]
headers = RequestHead -> [(HeaderName, Method)]
WS.requestHeaders (RequestHead -> [(HeaderName, Method)])
-> RequestHead -> [(HeaderName, Method)]
forall a b. (a -> b) -> a -> b
$ PendingConnection -> RequestHead
WS.pendingRequest PendingConnection
conn
case HeaderName -> [(HeaderName, Method)] -> Maybe Method
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup HeaderName
"Sec-WebSocket-Protocol" [(HeaderName, Method)]
headers of
Just Method
v
| Method
v Method -> Method -> Bool
forall a. Eq a => a -> a -> Bool
== Method
"graphql-ws" Bool -> Bool -> Bool
|| Method
v Method -> Method -> Bool
forall a. Eq a => a -> a -> Bool
== Method
"graphql-transport-ws"
-> do Connection
conn' <- PendingConnection -> AcceptRequest -> IO Connection
WS.acceptRequestWith PendingConnection
conn (Maybe Method -> [(HeaderName, Method)] -> AcceptRequest
WS.AcceptRequest (Method -> Maybe Method
forall a. a -> Maybe a
Just Method
v) [])
((Maybe Text
-> VariableMapC
-> [Definition]
-> ConduitT Value Void IO ()
-> IO ())
-> Connection -> IO ())
-> Connection
-> (Maybe Text
-> VariableMapC
-> [Definition]
-> ConduitT Value Void IO ()
-> IO ())
-> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Maybe Text
-> VariableMapC
-> [Definition]
-> ConduitT Value Void IO ()
-> IO ())
-> Connection -> IO ()
protocol Connection
conn' ((Maybe Text
-> VariableMapC
-> [Definition]
-> ConduitT Value Void IO ()
-> IO ())
-> IO ())
-> (Maybe Text
-> VariableMapC
-> [Definition]
-> ConduitT Value Void IO ()
-> IO ())
-> IO ()
forall a b. (a -> b) -> a -> b
$
(forall a. m a -> ServerErrorIO a)
-> [(HeaderName, Method)]
-> ServerT chn Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> Maybe Text
-> VariableMapC
-> [Definition]
-> ConduitT Value Void IO ()
-> IO ()
forall (qr :: Maybe Symbol) (mut :: Maybe Symbol)
(sub :: Maybe Symbol) (p :: Package') (m :: * -> *)
(chn :: ServiceChain Symbol) (hs :: [[*]]).
GraphQLApp p qr mut sub m chn hs =>
(forall a. m a -> ServerErrorIO a)
-> [(HeaderName, Method)]
-> ServerT chn Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> Maybe Text
-> VariableMapC
-> [Definition]
-> ConduitT Value Void IO ()
-> IO ()
runSubscriptionPipeline forall a. m a -> ServerErrorIO a
f [(HeaderName, Method)]
headers ServerT chn Field p m hs
server Proxy qr
q Proxy mut
m Proxy sub
s
Maybe Method
_ -> PendingConnection -> Method -> IO ()
WS.rejectRequest PendingConnection
conn Method
"unsupported protocol"
runGraphQLAppSettings ::
( GraphQLApp p qr mut sub ServerErrorIO chn hs )
=> Settings
-> ServerT chn GQL.Field p ServerErrorIO hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> IO ()
runGraphQLAppSettings :: Settings
-> ServerT chn Field p ServerErrorIO hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> IO ()
runGraphQLAppSettings Settings
st ServerT chn Field p ServerErrorIO hs
svr Proxy qr
q Proxy mut
m Proxy sub
s = Settings -> Application -> IO ()
runSettings Settings
st (ServerT chn Field p ServerErrorIO hs
-> Proxy qr -> Proxy mut -> Proxy sub -> Application
forall (p :: Package') (qr :: Maybe Symbol) (mut :: Maybe Symbol)
(sub :: Maybe Symbol) (chn :: ServiceChain Symbol) (hs :: [[*]]).
GraphQLApp p qr mut sub ServerErrorIO chn hs =>
ServerT chn Field p ServerErrorIO hs
-> Proxy qr -> Proxy mut -> Proxy sub -> Application
graphQLApp ServerT chn Field p ServerErrorIO hs
svr Proxy qr
q Proxy mut
m Proxy sub
s)
runGraphQLApp ::
( GraphQLApp p qr mut sub ServerErrorIO chn hs )
=> Port
-> ServerT chn GQL.Field p ServerErrorIO hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> IO ()
runGraphQLApp :: Port
-> ServerT chn Field p ServerErrorIO hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> IO ()
runGraphQLApp Port
port ServerT chn Field p ServerErrorIO hs
svr Proxy qr
q Proxy mut
m Proxy sub
s = Port -> Application -> IO ()
run Port
port (ServerT chn Field p ServerErrorIO hs
-> Proxy qr -> Proxy mut -> Proxy sub -> Application
forall (p :: Package') (qr :: Maybe Symbol) (mut :: Maybe Symbol)
(sub :: Maybe Symbol) (chn :: ServiceChain Symbol) (hs :: [[*]]).
GraphQLApp p qr mut sub ServerErrorIO chn hs =>
ServerT chn Field p ServerErrorIO hs
-> Proxy qr -> Proxy mut -> Proxy sub -> Application
graphQLApp ServerT chn Field p ServerErrorIO hs
svr Proxy qr
q Proxy mut
m Proxy sub
s)
runGraphQLAppTrans ::
( GraphQLApp p qr mut sub m chn hs )
=> Port
-> (forall a. m a -> ServerErrorIO a)
-> ServerT chn GQL.Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> IO ()
runGraphQLAppTrans :: Port
-> (forall a. m a -> ServerErrorIO a)
-> ServerT chn Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> IO ()
runGraphQLAppTrans Port
port forall a. m a -> ServerErrorIO a
f ServerT chn Field p m hs
svr Proxy qr
q Proxy mut
m Proxy sub
s = Port -> Application -> IO ()
run Port
port ((forall a. m a -> ServerErrorIO a)
-> ServerT chn Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> Application
forall (p :: Package') (qr :: Maybe Symbol) (mut :: Maybe Symbol)
(sub :: Maybe Symbol) (m :: * -> *) (chn :: ServiceChain Symbol)
(hs :: [[*]]).
GraphQLApp p qr mut sub m chn hs =>
(forall a. m a -> ServerErrorIO a)
-> ServerT chn Field p m hs
-> Proxy qr
-> Proxy mut
-> Proxy sub
-> Application
graphQLAppTrans forall a. m a -> ServerErrorIO a
f ServerT chn Field p m hs
svr Proxy qr
q Proxy mut
m Proxy sub
s)
runGraphQLAppQuery ::
( GraphQLApp p ('Just qr) 'Nothing 'Nothing ServerErrorIO chn hs )
=> Port
-> ServerT chn GQL.Field p ServerErrorIO hs
-> Proxy qr
-> IO ()
runGraphQLAppQuery :: Port -> ServerT chn Field p ServerErrorIO hs -> Proxy qr -> IO ()
runGraphQLAppQuery Port
port ServerT chn Field p ServerErrorIO hs
svr Proxy qr
q = Port -> Application -> IO ()
run Port
port (ServerT chn Field p ServerErrorIO hs -> Proxy qr -> Application
forall (qr :: Symbol) (p :: Package') (chn :: ServiceChain Symbol)
(hs :: [[*]]).
GraphQLApp p ('Just qr) 'Nothing 'Nothing ServerErrorIO chn hs =>
ServerT chn Field p ServerErrorIO hs -> Proxy qr -> Application
graphQLAppQuery ServerT chn Field p ServerErrorIO hs
svr Proxy qr
q)
liftServerConduit
:: MonadIO m
=> ConduitT i o ServerErrorIO r -> ConduitT i o m r
liftServerConduit :: ConduitT i o ServerErrorIO r -> ConduitT i o m r
liftServerConduit = (forall a. ServerErrorIO a -> m a)
-> ConduitT i o ServerErrorIO r -> ConduitT i o m r
forall (m :: * -> *) (n :: * -> *) i o r.
Monad m =>
(forall a. m a -> n a) -> ConduitT i o m r -> ConduitT i o n r
transPipe forall a. ServerErrorIO a -> m a
forall (m :: * -> *) a. MonadIO m => ServerErrorIO a -> m a
raiseErrors
where raiseErrors :: forall m a. MonadIO m => ServerErrorIO a -> m a
raiseErrors :: ServerErrorIO a -> m a
raiseErrors ServerErrorIO a
h
= IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> m a) -> IO a -> m a
forall a b. (a -> b) -> a -> b
$ do
Either ServerError a
h' <- ServerErrorIO a -> IO (Either ServerError a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ServerErrorIO a
h
case Either ServerError a
h' of
Right a
r -> a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
r
Left ServerError
e -> ServerError -> IO a
forall a e. Exception e => e -> a
throw ServerError
e