morpheus-graphql-client-0.27.0: Morpheus GraphQL Client
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Morpheus.Client

Synopsis

Documentation

raw :: QuasiQuoter Source #

QuasiQuoter to insert multiple lines of text in Haskell

class (RequestType a, ToJSON (Args a), FromJSON a) => Fetch a where Source #

Associated Types

type Args a :: Type Source #

Methods

fetch :: Monad m => (ByteString -> m ByteString) -> Args a -> m (Either (FetchError a) a) Source #

Instances

Instances details
(RequestType a, ToJSON (Args a), FromJSON a) => Fetch a Source # 
Instance details

Defined in Data.Morpheus.Client.Fetch

Associated Types

type Args a Source #

Methods

fetch :: Monad m => (ByteString -> m ByteString) -> Args a -> m (Either (FetchError a) a) Source #

data FetchError a Source #

Instances

Instances details
Generic (FetchError a) Source # 
Instance details

Defined in Data.Morpheus.Client.Fetch.Types

Associated Types

type Rep (FetchError a) :: Type -> Type #

Methods

from :: FetchError a -> Rep (FetchError a) x #

to :: Rep (FetchError a) x -> FetchError a #

Show a => Show (FetchError a) Source # 
Instance details

Defined in Data.Morpheus.Client.Fetch.Types

Eq a => Eq (FetchError a) Source # 
Instance details

Defined in Data.Morpheus.Client.Fetch.Types

Methods

(==) :: FetchError a -> FetchError a -> Bool #

(/=) :: FetchError a -> FetchError a -> Bool #

type Rep (FetchError a) Source # 
Instance details

Defined in Data.Morpheus.Client.Fetch.Types

type Rep (FetchError a) = D1 ('MetaData "FetchError" "Data.Morpheus.Client.Fetch.Types" "morpheus-graphql-client-0.27.0-5azuRqPYpKn3QKKXExR1lT" 'False) (C1 ('MetaCons "FetchErrorParseFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "FetchErrorProducedErrors" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GQLErrors) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a))) :+: C1 ('MetaCons "FetchErrorNoResult" 'PrefixI 'False) (U1 :: Type -> Type)))

data ScalarValue #

Primitive Values for GQLScalar: ScalarValue, ScalarValue, ScalarValue, Boolean. for performance reason type Text represents GraphQl ScalarValue value

Instances

Instances details
FromJSON ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

ToJSON ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

IsString ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Generic ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Associated Types

type Rep ScalarValue :: Type -> Type #

Show ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Eq ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

RenderGQL ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Methods

renderGQL :: ScalarValue -> Rendering #

Lift ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Methods

lift :: Quote m => ScalarValue -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ScalarValue -> Code m ScalarValue #

type Rep ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

class DecodeScalar a where #

GraphQL Scalar parser

class EncodeScalar a where #

GraphQL Scalar Serializer

Methods

encodeScalar :: a -> ScalarValue #

Instances

Instances details
EncodeScalar ID 
Instance details

Defined in Data.Morpheus.Types.ID

EncodeScalar Text 
Instance details

Defined in Data.Morpheus.Types.GQLScalar

EncodeScalar Bool 
Instance details

Defined in Data.Morpheus.Types.GQLScalar

EncodeScalar Double 
Instance details

Defined in Data.Morpheus.Types.GQLScalar

EncodeScalar Float 
Instance details

Defined in Data.Morpheus.Types.GQLScalar

EncodeScalar Int 
Instance details

Defined in Data.Morpheus.Types.GQLScalar

newtype ID #

default GraphQL type, parses only ScalarValue and ScalarValue values, serialized always as ScalarValue

Constructors

ID 

Fields

Instances

Instances details
FromJSON ID 
Instance details

Defined in Data.Morpheus.Types.ID

ToJSON ID 
Instance details

Defined in Data.Morpheus.Types.ID

IsString ID 
Instance details

Defined in Data.Morpheus.Types.ID

Methods

fromString :: String -> ID #

Semigroup ID 
Instance details

Defined in Data.Morpheus.Types.ID

Methods

(<>) :: ID -> ID -> ID #

sconcat :: NonEmpty ID -> ID #

stimes :: Integral b => b -> ID -> ID #

Generic ID 
Instance details

Defined in Data.Morpheus.Types.ID

Associated Types

type Rep ID :: Type -> Type #

Methods

from :: ID -> Rep ID x #

to :: Rep ID x -> ID #

Show ID 
Instance details

Defined in Data.Morpheus.Types.ID

Methods

showsPrec :: Int -> ID -> ShowS #

show :: ID -> String #

showList :: [ID] -> ShowS #

Eq ID 
Instance details

Defined in Data.Morpheus.Types.ID

Methods

(==) :: ID -> ID -> Bool #

(/=) :: ID -> ID -> Bool #

Hashable ID 
Instance details

Defined in Data.Morpheus.Types.ID

Methods

hashWithSalt :: Int -> ID -> Int #

hash :: ID -> Int #

DecodeScalar ID 
Instance details

Defined in Data.Morpheus.Types.ID

EncodeScalar ID 
Instance details

Defined in Data.Morpheus.Types.ID

type Rep ID 
Instance details

Defined in Data.Morpheus.Types.ID

type Rep ID = D1 ('MetaData "ID" "Data.Morpheus.Types.ID" "morpheus-graphql-core-0.27.0-6kwLaZNKUDnI7xQD4dSyYD" 'True) (C1 ('MetaCons "ID" 'PrefixI 'True) (S1 ('MetaSel ('Just "unpackID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

declareGlobalTypes Source #

Arguments

:: FilePath

the schema path relative to the project location, both introspection (.json) and schema definition (.gql, .graphql) are accepted.

-> Q [Dec] 

declares input, enum and scalar types for specified schema

Example where the schema is defined in SDL format

declareGlobalTypes "schema.gql"

Example with schema as introspection in JSON format.

declareGlobalTypes "schema.json"

declareGlobalTypesByName :: FilePath -> [TypeName] -> Q [Dec] Source #

declares global types like declareGlobalTypes, while enabling to select only the types that are needed.

declareLocalTypes Source #

Arguments

:: FilePath

the schema path relative to the project location. both introspection (`.json`) and schema definition (`.gql`, `.graphql`) are accepted.

-> FilePath

query path relative to the project location

-> Q [Dec] 

declares object, interface and union types for specified schema and query.

Example where the schema is defined in SDL format

declareLocalTypes "schema.gql" "query.gql"

Example with schema as introspection in JSON format.

declareLocalTypes "schema.json" "query.gql"

declareLocalTypesInline Source #

Arguments

:: FilePath

the schema path relative to the project location. both introspection (`.json`) and schema definition (`.gql`, `.graphql`) are accepted.

-> ExecutableSource

inline graphql query in Text format

-> Q [Dec] 

inline version of declareLocalTypes, however instead of specifying the file path, you can simply pass the query as text using QuasiQuoter raw

declareLocalTypesInline "schema.gql"
    [raw|
       query GetUsers {
          users {
            name
          }
       }
    ]
 

clientTypeDeclarations :: SchemaSource -> Maybe ExecutableSource -> Q [Dec] Source #

declares global or local types, depending on whether the second argument is specified or not

data GQLClient Source #

Instances

Instances details
IsString GQLClient Source # 
Instance details

Defined in Data.Morpheus.Client.Fetch.GQLClient

request :: (ClientTypeConstraint a, MonadFail m) => GQLClient -> Args a -> m (ResponseStream a) Source #

forEach :: (MonadIO m, MonadUnliftIO m, MonadFail m) => (GQLClientResult a -> m ()) -> ResponseStream a -> m () Source #

returns loop listening subscription events forever. if you want to run it in background use forkIO

single :: MonadIO m => ResponseStream a -> m (GQLClientResult a) Source #

returns first response from the server

class RequestType a where Source #

Associated Types

type RequestArgs a :: Type Source #

Methods

__name :: f a -> FieldName Source #

__query :: f a -> String Source #

__type :: f a -> OperationType Source #