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

module Data.Morpheus.Client.Internal.Types
  ( ClientTypeDefinition (..),
    TypeNameTH (..),
    FetchDefinition (..),
    ClientConstructorDefinition (..),
    FetchError (..),
    SchemaSource (..),
    ExecutableSource,
    GQLClientResult,
  )
where

import Data.ByteString.Lazy (ByteString)
import Data.Morpheus.Types.Internal.AST
  ( ANY,
    FieldDefinition,
    FieldName,
    GQLErrors,
    OperationType,
    TypeKind,
    TypeName,
    VALID,
  )
import Relude hiding (ByteString)

data TypeNameTH = TypeNameTH
  { TypeNameTH -> [FieldName]
namespace :: [FieldName],
    TypeNameTH -> TypeName
typename :: TypeName
  }
  deriving (Int -> TypeNameTH -> ShowS
[TypeNameTH] -> ShowS
TypeNameTH -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypeNameTH] -> ShowS
$cshowList :: [TypeNameTH] -> ShowS
show :: TypeNameTH -> String
$cshow :: TypeNameTH -> String
showsPrec :: Int -> TypeNameTH -> ShowS
$cshowsPrec :: Int -> TypeNameTH -> ShowS
Show)

data ClientConstructorDefinition = ClientConstructorDefinition
  { ClientConstructorDefinition -> TypeName
cName :: TypeName,
    ClientConstructorDefinition -> [FieldDefinition ANY VALID]
cFields :: [FieldDefinition ANY VALID]
  }
  deriving (Int -> ClientConstructorDefinition -> ShowS
[ClientConstructorDefinition] -> ShowS
ClientConstructorDefinition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClientConstructorDefinition] -> ShowS
$cshowList :: [ClientConstructorDefinition] -> ShowS
show :: ClientConstructorDefinition -> String
$cshow :: ClientConstructorDefinition -> String
showsPrec :: Int -> ClientConstructorDefinition -> ShowS
$cshowsPrec :: Int -> ClientConstructorDefinition -> ShowS
Show)

data ClientTypeDefinition = ClientTypeDefinition
  { ClientTypeDefinition -> TypeNameTH
clientTypeName :: TypeNameTH,
    ClientTypeDefinition -> [ClientConstructorDefinition]
clientCons :: [ClientConstructorDefinition],
    ClientTypeDefinition -> TypeKind
clientKind :: TypeKind
  }
  deriving (Int -> ClientTypeDefinition -> ShowS
[ClientTypeDefinition] -> ShowS
ClientTypeDefinition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClientTypeDefinition] -> ShowS
$cshowList :: [ClientTypeDefinition] -> ShowS
show :: ClientTypeDefinition -> String
$cshow :: ClientTypeDefinition -> String
showsPrec :: Int -> ClientTypeDefinition -> ShowS
$cshowsPrec :: Int -> ClientTypeDefinition -> ShowS
Show)

data FetchDefinition = FetchDefinition
  { FetchDefinition -> TypeNameTH
rootTypeName :: TypeNameTH,
    FetchDefinition -> Maybe TypeNameTH
clientArgumentsTypeName :: Maybe TypeNameTH,
    FetchDefinition -> OperationType
fetchOperationType :: OperationType
  }
  deriving (Int -> FetchDefinition -> ShowS
[FetchDefinition] -> ShowS
FetchDefinition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FetchDefinition] -> ShowS
$cshowList :: [FetchDefinition] -> ShowS
show :: FetchDefinition -> String
$cshow :: FetchDefinition -> String
showsPrec :: Int -> FetchDefinition -> ShowS
$cshowsPrec :: Int -> FetchDefinition -> ShowS
Show)

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

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

type ExecutableSource = Text

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