Fix spaces

This commit is contained in:
Alejandro Serrano 2023-01-08 08:35:28 +01:00
parent e2dcb98ace
commit 4e2412efa8
3 changed files with 19 additions and 19 deletions

View File

@ -11,7 +11,7 @@
{-# language TypeOperators #-}
{-# language UndecidableInstances #-}
{-# language ViewPatterns #-}
{-# OPTIONS_GHC -Wincomplete-patterns -fno-warn-orphans #-}
{-# OPTIONS_GHC -Wincomplete-patterns -fno-warn-orphans #-}
module Mu.GraphQL.Query.Parse where
@ -353,7 +353,7 @@ instance ( ParseMethod p ('Service s methods) methods, KnownName s )
go (GQL.InlineFragmentSelection (GQL.InlineFragment ty dirs innerSs _) : ss)
| any (shouldSkip vmap) dirs
= go ss
| Nothing <- ty
| Nothing <- ty
= go (F.toList innerSs ++ ss)
| Just selectedTy <- ty
= let thisTy = T.pack (nameVal (Proxy @s))
@ -518,19 +518,19 @@ class ParseMaybeArg (p :: Package') (a :: TypeRef Symbol) where
-> Maybe GQL.Value
-> f (ArgumentValue' p a)
instance {-# OVERLAPS #-} (ParseArg p a)
instance {-# OVERLAPS #-} (ParseArg p a)
=> ParseMaybeArg p ('OptionalRef a) where
parseMaybeArg vmap aname (Just x)
= ArgOptional . Just <$> parseArg' vmap aname x
parseMaybeArg _ _ Nothing
= pure $ ArgOptional Nothing
instance {-# OVERLAPS #-} (ParseArg p a)
instance {-# OVERLAPS #-} (ParseArg p a)
=> ParseMaybeArg p ('ListRef a) where
parseMaybeArg vmap aname (Just x)
= parseArg' vmap aname x
parseMaybeArg _ _ Nothing
= pure $ ArgList []
instance {-# OVERLAPPABLE #-} (ParseArg p a)
instance {-# OVERLAPPABLE #-} (ParseArg p a)
=> ParseMaybeArg p a where
parseMaybeArg vmap aname (Just x)
= parseArg' vmap aname x
@ -816,7 +816,7 @@ instance (KnownName name, ParseField sch fields)
parseSchemaQuery ::
forall (sch :: Schema') t (rname :: Symbol) fields f.
( MonadError T.Text f
, t ~  'DRecord rname fields
, t ~ 'DRecord rname fields
, KnownName rname
, ParseField sch fields ) =>
Proxy sch ->

View File

@ -14,7 +14,7 @@
{-# language TypeFamilies #-}
{-# language TypeOperators #-}
{-# language UndecidableInstances #-}
{-# OPTIONS_GHC -fprint-explicit-foralls #-}
{-# OPTIONS_GHC -fprint-explicit-foralls #-}
module Mu.GraphQL.Query.Run (
GraphQLApp
, runPipeline
@ -267,7 +267,7 @@ runSubscription f req whole@(Services ss) path
class RunQueryFindHandler m p whole chn ss s hs where
runQueryFindHandler
:: ( p ~ 'Package pname wholess
:: ( p ~ 'Package pname wholess
, inh ~ MappingRight chn (ServiceName s) )
=> (forall a. m a -> ServerErrorIO a)
-> RequestHeaders
@ -278,7 +278,7 @@ class RunQueryFindHandler m p whole chn ss s hs where
-> ServiceQuery p s
-> WriterT [GraphQLError] IO Aeson.Value
runSubscriptionFindHandler
:: ( p ~ 'Package pname wholess
:: ( p ~ 'Package pname wholess
, inh ~ MappingRight chn (ServiceName s) )
=> (forall a. m a -> ServerErrorIO a)
-> RequestHeaders
@ -293,7 +293,7 @@ class RunQueryFindHandler m p whole chn ss s hs where
class RunQueryOnFoundHandler m p whole chn (s :: Service snm mnm anm (TypeRef snm)) hs where
type ServiceName s :: snm
runQueryOnFoundHandler
:: ( p ~ 'Package pname wholess
:: ( p ~ 'Package pname wholess
, inh ~ MappingRight chn (ServiceName s) )
=> (forall a. m a -> ServerErrorIO a)
-> RequestHeaders
@ -304,7 +304,7 @@ class RunQueryOnFoundHandler m p whole chn (s :: Service snm mnm anm (TypeRef sn
-> ServiceQuery p s
-> WriterT [GraphQLError] IO Aeson.Value
runSubscriptionOnFoundHandler
:: ( p ~ 'Package pname wholess
:: ( p ~ 'Package pname wholess
, inh ~ MappingRight chn (ServiceName s) )
=> (forall a. m a -> ServerErrorIO a)
-> RequestHeaders
@ -320,7 +320,7 @@ instance TypeError ('Text "Could not find handler for " ':<>: 'ShowType s)
=> RunQueryFindHandler m p whole chn '[] s '[] where
runQueryFindHandler _ = error "this should never be called"
runSubscriptionFindHandler _ = error "this should never be called"
instance {-# OVERLAPPABLE #-}
instance {-# OVERLAPPABLE #-}
RunQueryFindHandler m p whole chn ss s hs
=> RunQueryFindHandler m p whole chn (other ': ss) s (h ': hs) where
runQueryFindHandler f req sch whole path (_ :<&>: that)
@ -416,8 +416,8 @@ instance forall m p pname s sname whole ss chn elts.
class RunMethod m p whole chn s ms hs where
runMethod
:: ( p ~ 'Package pname wholess
, inh ~ MappingRight chn (ServiceName s) )
:: ( p ~ 'Package pname wholess
, inh ~ MappingRight chn (ServiceName s) )
=> (forall a. m a -> ServerErrorIO a)
-> RequestHeaders
-> ServerT chn GQL.Field p m whole
@ -426,8 +426,8 @@ class RunMethod m p whole chn s ms hs where
-> NS (ChosenMethodQuery p) ms
-> WriterT [GraphQLError] IO (Maybe (T.Text, Aeson.Value))
runMethodSubscription
:: ( p ~ 'Package pname wholess
, inh ~ MappingRight chn (ServiceName s) )
:: ( p ~ 'Package pname wholess
, inh ~ MappingRight chn (ServiceName s) )
=> (forall a. m a -> ServerErrorIO a)
-> RequestHeaders
-> ServerT chn GQL.Field p m whole

View File

@ -111,12 +111,12 @@ data ClientMessage
data ServerMessage
= GQLConnectionError { errorPayload :: Maybe A.Value }
| GQLConnectionAck
| GQLData { serverMsgId :: T.Text
| GQLData { serverMsgId :: T.Text
, payload :: A.Value }
| GQLError { serverMsgId :: T.Text
| GQLError { serverMsgId :: T.Text
, payload :: A.Value }
| GQLComplete { serverMsgId :: T.Text}
| GQLKeepAlive
| GQLKeepAlive
deriving Show
-- NOTE: using https://github.com/apollographql/subscriptions-transport-ws/blob/master/src/message-types.ts