-- | Internal API error type

{-# LANGUAGE RecordWildCards #-}

{-# OPTIONS_HADDOCK hide #-}

module Blockfrost.Types.ApiError
  ( ApiError (..)
  ) where

import Data.Aeson
import Data.Text (Text)
import GHC.Generics

-- | Fancy JSON error returned
-- by the server
data ApiError = ApiError
  { ApiError -> Text
apiError        :: Text
  , ApiError -> Text
apiErrorMessage :: Text
  , ApiError -> Int
apiErrorCode    :: Int
  } deriving (ApiError -> ApiError -> Bool
(ApiError -> ApiError -> Bool)
-> (ApiError -> ApiError -> Bool) -> Eq ApiError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApiError -> ApiError -> Bool
$c/= :: ApiError -> ApiError -> Bool
== :: ApiError -> ApiError -> Bool
$c== :: ApiError -> ApiError -> Bool
Eq, Int -> ApiError -> ShowS
[ApiError] -> ShowS
ApiError -> String
(Int -> ApiError -> ShowS)
-> (ApiError -> String) -> ([ApiError] -> ShowS) -> Show ApiError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApiError] -> ShowS
$cshowList :: [ApiError] -> ShowS
show :: ApiError -> String
$cshow :: ApiError -> String
showsPrec :: Int -> ApiError -> ShowS
$cshowsPrec :: Int -> ApiError -> ShowS
Show, (forall x. ApiError -> Rep ApiError x)
-> (forall x. Rep ApiError x -> ApiError) -> Generic ApiError
forall x. Rep ApiError x -> ApiError
forall x. ApiError -> Rep ApiError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ApiError x -> ApiError
$cfrom :: forall x. ApiError -> Rep ApiError x
Generic)

instance ToJSON ApiError  where
  toJSON :: ApiError -> Value
toJSON ApiError{Int
Text
apiErrorCode :: Int
apiErrorMessage :: Text
apiError :: Text
apiErrorCode :: ApiError -> Int
apiErrorMessage :: ApiError -> Text
apiError :: ApiError -> Text
..} =
    [Pair] -> Value
object [ Text
"error" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
apiError
           , Text
"message" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
apiErrorMessage
           , Text
"status_code" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Int -> Value
forall a. ToJSON a => a -> Value
toJSON Int
apiErrorCode
           ]

instance FromJSON ApiError  where
  parseJSON :: Value -> Parser ApiError
parseJSON = String -> (Object -> Parser ApiError) -> Value -> Parser ApiError
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"error" ((Object -> Parser ApiError) -> Value -> Parser ApiError)
-> (Object -> Parser ApiError) -> Value -> Parser ApiError
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    Text
apiError <- Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"error"
    Text
apiErrorMessage <- Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"message"
    Int
apiErrorCode <- Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"status_code"
    ApiError -> Parser ApiError
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ApiError -> Parser ApiError) -> ApiError -> Parser ApiError
forall a b. (a -> b) -> a -> b
$ ApiError :: Text -> Text -> Int -> ApiError
ApiError {Int
Text
apiErrorCode :: Int
apiErrorMessage :: Text
apiError :: Text
apiErrorCode :: Int
apiErrorMessage :: Text
apiError :: Text
..}