{-# LANGUAGE ConstrainedClassMethods #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE NoImplicitPrelude #-} module Data.Morpheus.Client.Fetch ( Fetch (..), decodeResponse, ) where import Data.Aeson ( FromJSON, ToJSON (..), eitherDecode, encode, ) import Data.ByteString.Lazy (ByteString) import Data.Morpheus.Client.Fetch.RequestType (Request (Request), RequestType (RequestArgs), processResponse, toRequest) import Data.Morpheus.Client.Fetch.Types ( FetchError (..), ) import Relude hiding (ByteString) decodeResponse :: FromJSON a => ByteString -> Either (FetchError a) a decodeResponse :: forall a. FromJSON a => ByteString -> Either (FetchError a) a decodeResponse = ((String -> FetchError a) -> Either String (JSONResponse a) -> Either (FetchError a) (JSONResponse a) forall a b c. (a -> b) -> Either a c -> Either b c forall (p :: * -> * -> *) a b c. Bifunctor p => (a -> b) -> p a c -> p b c first String -> FetchError a forall a. String -> FetchError a FetchErrorParseFailure (Either String (JSONResponse a) -> Either (FetchError a) (JSONResponse a)) -> (ByteString -> Either String (JSONResponse a)) -> ByteString -> Either (FetchError a) (JSONResponse a) forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> Either String (JSONResponse a) forall a. FromJSON a => ByteString -> Either String a eitherDecode) (ByteString -> Either (FetchError a) (JSONResponse a)) -> (JSONResponse a -> Either (FetchError a) a) -> ByteString -> Either (FetchError a) a forall (m :: * -> *) a b c. Monad m => (a -> m b) -> (b -> m c) -> a -> m c >=> JSONResponse a -> Either (FetchError a) a forall a. JSONResponse a -> Either (FetchError a) a processResponse class (RequestType a, ToJSON (Args a), FromJSON a) => Fetch a where type Args a :: Type fetch :: Monad m => (ByteString -> m ByteString) -> Args a -> m (Either (FetchError a) a) instance (RequestType a, ToJSON (Args a), FromJSON a) => Fetch a where type Args a = RequestArgs a fetch :: forall (m :: * -> *). Monad m => (ByteString -> m ByteString) -> Args a -> m (Either (FetchError a) a) fetch ByteString -> m ByteString f Args a args = ByteString -> Either (FetchError a) a forall a. FromJSON a => ByteString -> Either (FetchError a) a decodeResponse (ByteString -> Either (FetchError a) a) -> m ByteString -> m (Either (FetchError a) a) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ByteString -> m ByteString f (GQLRequest -> ByteString forall a. ToJSON a => a -> ByteString encode (GQLRequest -> ByteString) -> GQLRequest -> ByteString forall a b. (a -> b) -> a -> b $ Request a -> GQLRequest forall a. (RequestType a, ToJSON (RequestArgs a)) => Request a -> GQLRequest toRequest Request a request) where request :: Request a request :: Request a request = RequestArgs a -> Request a forall a. RequestArgs a -> Request a Request RequestArgs a Args a args