{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NoImplicitPrelude #-} module Data.Morpheus.App.MapAPI ( MapAPI (..), ) where import Data.Aeson ( encode, ) import Data.Aeson.Internal ( formatError, ifromJSON, ) import Data.Aeson.Parser ( eitherDecodeWith, jsonNoDup, ) import qualified Data.ByteString.Lazy.Char8 as LB ( ByteString, fromStrict, toStrict, ) import Data.Morpheus.App.Error (badRequestError) import Data.Morpheus.Internal.Utils ( Failure (..), ) import Data.Morpheus.Types.IO ( GQLRequest (..), GQLResponse (..), ) import qualified Data.Text.Lazy as LT ( Text, fromStrict, toStrict, ) import Data.Text.Lazy.Encoding ( decodeUtf8, encodeUtf8, ) import Relude hiding ( decodeUtf8, encodeUtf8, ) decodeNoDup :: Failure String m => LB.ByteString -> m GQLRequest decodeNoDup :: ByteString -> m GQLRequest decodeNoDup ByteString str = case Parser Value -> (Value -> IResult GQLRequest) -> ByteString -> Either (JSONPath, String) GQLRequest forall a. Parser Value -> (Value -> IResult a) -> ByteString -> Either (JSONPath, String) a eitherDecodeWith Parser Value jsonNoDup Value -> IResult GQLRequest forall a. FromJSON a => Value -> IResult a ifromJSON ByteString str of Left (JSONPath path, String x) -> String -> m GQLRequest forall error (f :: * -> *) v. Failure error f => error -> f v failure (String -> m GQLRequest) -> String -> m GQLRequest forall a b. (a -> b) -> a -> b $ JSONPath -> String -> String formatError JSONPath path String x Right GQLRequest value -> GQLRequest -> m GQLRequest forall (f :: * -> *) a. Applicative f => a -> f a pure GQLRequest value class MapAPI a b where mapAPI :: Applicative m => (GQLRequest -> m GQLResponse) -> a -> m b instance MapAPI GQLRequest GQLResponse where mapAPI :: (GQLRequest -> m GQLResponse) -> GQLRequest -> m GQLResponse mapAPI GQLRequest -> m GQLResponse f = GQLRequest -> m GQLResponse f instance MapAPI LB.ByteString LB.ByteString where mapAPI :: (GQLRequest -> m GQLResponse) -> ByteString -> m ByteString mapAPI GQLRequest -> m GQLResponse api ByteString request = case ByteString -> Either String GQLRequest forall (m :: * -> *). Failure String m => ByteString -> m GQLRequest decodeNoDup ByteString request of Left String aesonError -> ByteString -> m ByteString forall (f :: * -> *) a. Applicative f => a -> f a pure (ByteString -> m ByteString) -> ByteString -> m ByteString forall a b. (a -> b) -> a -> b $ String -> ByteString badRequestError String aesonError Right GQLRequest req -> GQLResponse -> ByteString forall a. ToJSON a => a -> ByteString encode (GQLResponse -> ByteString) -> m GQLResponse -> m ByteString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> GQLRequest -> m GQLResponse api GQLRequest req instance MapAPI LT.Text LT.Text where mapAPI :: (GQLRequest -> m GQLResponse) -> Text -> m Text mapAPI GQLRequest -> m GQLResponse api = (ByteString -> Text) -> m ByteString -> m Text forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ByteString -> Text decodeUtf8 (m ByteString -> m Text) -> (Text -> m ByteString) -> Text -> m Text forall b c a. (b -> c) -> (a -> b) -> a -> c . (GQLRequest -> m GQLResponse) -> ByteString -> m ByteString forall a b (m :: * -> *). (MapAPI a b, Applicative m) => (GQLRequest -> m GQLResponse) -> a -> m b mapAPI GQLRequest -> m GQLResponse api (ByteString -> m ByteString) -> (Text -> ByteString) -> Text -> m ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> ByteString encodeUtf8 instance MapAPI ByteString ByteString where mapAPI :: (GQLRequest -> m GQLResponse) -> ByteString -> m ByteString mapAPI GQLRequest -> m GQLResponse api = (ByteString -> ByteString) -> m ByteString -> m ByteString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ByteString -> ByteString LB.toStrict (m ByteString -> m ByteString) -> (ByteString -> m ByteString) -> ByteString -> m ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . (GQLRequest -> m GQLResponse) -> ByteString -> m ByteString forall a b (m :: * -> *). (MapAPI a b, Applicative m) => (GQLRequest -> m GQLResponse) -> a -> m b mapAPI GQLRequest -> m GQLResponse api (ByteString -> m ByteString) -> (ByteString -> ByteString) -> ByteString -> m ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> ByteString LB.fromStrict instance MapAPI Text Text where mapAPI :: (GQLRequest -> m GQLResponse) -> Text -> m Text mapAPI GQLRequest -> m GQLResponse api = (Text -> Text) -> m Text -> m Text forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap Text -> Text LT.toStrict (m Text -> m Text) -> (Text -> m Text) -> Text -> m Text forall b c a. (b -> c) -> (a -> b) -> a -> c . (GQLRequest -> m GQLResponse) -> Text -> m Text forall a b (m :: * -> *). (MapAPI a b, Applicative m) => (GQLRequest -> m GQLResponse) -> a -> m b mapAPI GQLRequest -> m GQLResponse api (Text -> m Text) -> (Text -> Text) -> Text -> m Text forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> Text LT.fromStrict