{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Servant.Client.Core.ClientError (
ClientError (..),
) where
import Prelude ()
import Prelude.Compat
import Control.DeepSeq
(NFData (..))
import Control.Exception
(SomeException (..))
import Control.Monad.Catch
(Exception)
import qualified Data.ByteString as BS
import Data.Text
(Text)
import Data.Typeable
(Typeable, typeOf)
import GHC.Generics
(Generic)
import Network.HTTP.Media
(MediaType)
import Network.HTTP.Types ()
import Servant.Client.Core.BaseUrl
import Servant.Client.Core.Internal
(mediaTypeRnf)
import Servant.Client.Core.Request
import Servant.Client.Core.Response
data ClientError =
FailureResponse (RequestF () (BaseUrl, BS.ByteString)) Response
| DecodeFailure Text Response
| UnsupportedContentType MediaType Response
| InvalidContentTypeHeader Response
| ConnectionError SomeException
deriving (Show, Generic, Typeable)
instance Eq ClientError where
FailureResponse req res == FailureResponse req' res' = req == req' && res == res'
DecodeFailure t r == DecodeFailure t' r' = t == t' && r == r'
UnsupportedContentType mt r == UnsupportedContentType mt' r' = mt == mt' && r == r'
InvalidContentTypeHeader r == InvalidContentTypeHeader r' = r == r'
ConnectionError exc == ConnectionError exc' = eqSomeException exc exc'
where
eqSomeException (SomeException a) (SomeException b) = typeOf a == typeOf b
FailureResponse {} == _ = False
DecodeFailure {} == _ = False
UnsupportedContentType {} == _ = False
InvalidContentTypeHeader {} == _ = False
ConnectionError {} == _ = False
instance Exception ClientError
instance NFData ClientError where
rnf (FailureResponse req res) = rnf req `seq` rnf res
rnf (DecodeFailure err res) = rnf err `seq` rnf res
rnf (UnsupportedContentType mt' res) = mediaTypeRnf mt' `seq` rnf res
rnf (InvalidContentTypeHeader res) = rnf res
rnf (ConnectionError err) = err `seq` rnf (show err)