{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE NoImplicitPrelude #-}

module Data.Morpheus.Client.Fetch.Types
  ( FetchError (..),
    SchemaSource (..),
    ExecutableSource,
    GQLClientResult,
  )
where

import Data.ByteString.Lazy (ByteString)
import Data.Morpheus.Types.Internal.AST
  ( GQLErrors,
  )
import Relude hiding (ByteString)

data FetchError a
  = FetchErrorParseFailure String
  | FetchErrorProducedErrors GQLErrors (Maybe a)
  | FetchErrorNoResult
  deriving (Int -> FetchError a -> ShowS
[FetchError a] -> ShowS
FetchError a -> String
(Int -> FetchError a -> ShowS)
-> (FetchError a -> String)
-> ([FetchError a] -> ShowS)
-> Show (FetchError a)
forall a. Show a => Int -> FetchError a -> ShowS
forall a. Show a => [FetchError a] -> ShowS
forall a. Show a => FetchError a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> FetchError a -> ShowS
showsPrec :: Int -> FetchError a -> ShowS
$cshow :: forall a. Show a => FetchError a -> String
show :: FetchError a -> String
$cshowList :: forall a. Show a => [FetchError a] -> ShowS
showList :: [FetchError a] -> ShowS
Show, FetchError a -> FetchError a -> Bool
(FetchError a -> FetchError a -> Bool)
-> (FetchError a -> FetchError a -> Bool) -> Eq (FetchError a)
forall a. Eq a => FetchError a -> FetchError a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => FetchError a -> FetchError a -> Bool
== :: FetchError a -> FetchError a -> Bool
$c/= :: forall a. Eq a => FetchError a -> FetchError a -> Bool
/= :: FetchError a -> FetchError a -> Bool
Eq, (forall x. FetchError a -> Rep (FetchError a) x)
-> (forall x. Rep (FetchError a) x -> FetchError a)
-> Generic (FetchError a)
forall x. Rep (FetchError a) x -> FetchError a
forall x. FetchError a -> Rep (FetchError a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (FetchError a) x -> FetchError a
forall a x. FetchError a -> Rep (FetchError a) x
$cfrom :: forall a x. FetchError a -> Rep (FetchError a) x
from :: forall x. FetchError a -> Rep (FetchError a) x
$cto :: forall a x. Rep (FetchError a) x -> FetchError a
to :: forall x. Rep (FetchError a) x -> FetchError a
Generic)

data SchemaSource
  = JSON ByteString
  | GQL ByteString
  deriving (Int -> SchemaSource -> ShowS
[SchemaSource] -> ShowS
SchemaSource -> String
(Int -> SchemaSource -> ShowS)
-> (SchemaSource -> String)
-> ([SchemaSource] -> ShowS)
-> Show SchemaSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SchemaSource -> ShowS
showsPrec :: Int -> SchemaSource -> ShowS
$cshow :: SchemaSource -> String
show :: SchemaSource -> String
$cshowList :: [SchemaSource] -> ShowS
showList :: [SchemaSource] -> ShowS
Show, SchemaSource -> SchemaSource -> Bool
(SchemaSource -> SchemaSource -> Bool)
-> (SchemaSource -> SchemaSource -> Bool) -> Eq SchemaSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SchemaSource -> SchemaSource -> Bool
== :: SchemaSource -> SchemaSource -> Bool
$c/= :: SchemaSource -> SchemaSource -> Bool
/= :: SchemaSource -> SchemaSource -> Bool
Eq)

type ExecutableSource = Text

type GQLClientResult (a :: Type) = (Either (FetchError a) a)