{-# OPTIONS_GHC -Wno-incomplete-patterns #-}
module Hreq.Core.Client.ClientError where
import Control.Exception (Exception, SomeException (..))
import Data.Text (Text)
import Data.Typeable (Typeable, typeOf)
import GHC.Generics (Generic)
import Network.HTTP.Media (MediaType)
import Hreq.Core.Client.Request
import Hreq.Core.Client.Response
data ClientError =
  
  
  
    FailureResponse Request 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
instance Exception ClientError