{-# LANGUAGE CPP, ScopedTypeVariables #-}
module Network.HTTP.Base
       (
          
         httpVersion                 
          
       , Request(..)
       , Response(..)
       , RequestMethod(..)
       , Request_String
       , Response_String
       , HTTPRequest
       , HTTPResponse
          
       , urlEncode
       , urlDecode
       , urlEncodeVars
          
       , URIAuthority(..)
       , parseURIAuthority
          
       , uriToAuthorityString   
       , uriAuthToString        
       , uriAuthPort            
       , reqURIAuth             
       , parseResponseHead      
       , parseRequestHead       
       , ResponseNextStep(..)
       , matchResponse
       , ResponseData
       , ResponseCode
       , RequestData
       , NormalizeRequestOptions(..)
       , defaultNormalizeRequestOptions 
       , RequestNormalizer
       , normalizeRequest   
       , splitRequestURI
       , getAuth
       , normalizeRequestURI
       , normalizeHostHeader
       , findConnClose
         
       , linearTransfer
       , hopefulTransfer
       , chunkedTransfer
       , uglyDeathTransfer
       , readTillEmpty1
       , readTillEmpty2
       , defaultGETRequest
       , defaultGETRequest_
       , mkRequest
       , setRequestBody
       , defaultUserAgent
       , httpPackageVersion
       , libUA  
       , catchIO
       , catchIO_
       , responseParseError
       , getRequestVersion
       , getResponseVersion
       , setRequestVersion
       , setResponseVersion
       , failHTTPS
       ) where
import Network.URI
   ( URI(uriAuthority, uriPath, uriScheme)
   , URIAuth(URIAuth, uriUserInfo, uriRegName, uriPort)
   , parseURIReference
   )
import Control.Monad ( guard )
import Control.Monad.Error.Class ()
import Data.Bits     ( (.&.), (.|.), shiftL, shiftR )
import Data.Word     ( Word8 )
import Data.Char     ( digitToInt, intToDigit, toLower, isDigit,
                       isAscii, isAlphaNum, ord, chr )
import Data.List     ( partition, find )
import Data.Maybe    ( listToMaybe, fromMaybe )
import Numeric       ( readHex )
import Network.Stream
import Network.BufferType ( BufferOp(..), BufferType(..) )
import Network.HTTP.Headers
import Network.HTTP.Utils ( trim, crlf, sp, readsOne )
import qualified Network.HTTP.Base64 as Base64 (encode)
import Text.Read.Lex (readDecP)
import Text.ParserCombinators.ReadP
   ( ReadP, readP_to_S, char, (<++), look, munch, munch1 )
import Control.Exception as Exception (catch, IOException)
import qualified Paths_HTTP as Self (version)
import Data.Version (showVersion)
data URIAuthority = URIAuthority { user :: Maybe String,
                                   password :: Maybe String,
                                   host :: String,
                                   port :: Maybe Int
                                 } deriving (Eq,Show)
parseURIAuthority :: String -> Maybe URIAuthority
parseURIAuthority s = listToMaybe (map fst (readP_to_S pURIAuthority s))
pURIAuthority :: ReadP URIAuthority
pURIAuthority = do
                (u,pw) <- (pUserInfo `before` char '@')
                          <++ return (Nothing, Nothing)
                h <- rfc2732host <++ munch (/=':')
                p <- orNothing (char ':' >> readDecP)
                look >>= guard . null
                return URIAuthority{ user=u, password=pw, host=h, port=p }
rfc2732host :: ReadP String
rfc2732host = do
    _ <- char '['
    res <- munch1 (/=']')
    _ <- char ']'
    return res
pUserInfo :: ReadP (Maybe String, Maybe String)
pUserInfo = do
            u <- orNothing (munch (`notElem` ":@"))
            p <- orNothing (char ':' >> munch (/='@'))
            return (u,p)
before :: Monad m => m a -> m b -> m a
before a b = a >>= \x -> b >> return x
orNothing :: ReadP a -> ReadP (Maybe a)
orNothing p = fmap Just p <++ return Nothing
uriToAuthorityString :: URI -> String
uriToAuthorityString u = maybe "" uriAuthToString (uriAuthority u)
uriAuthToString :: URIAuth -> String
uriAuthToString ua =
  concat [ uriUserInfo ua
         , uriRegName ua
         , uriPort ua
         ]
uriAuthPort :: Maybe URI -> URIAuth -> Int
uriAuthPort mbURI u =
  case uriPort u of
    (':':s) -> readsOne id (default_port mbURI) s
    _       -> default_port mbURI
 where
  default_port Nothing = default_http
  default_port (Just url) =
    case map toLower $ uriScheme url of
      "http:" -> default_http
      "https:" -> default_https
        
      _ -> default_http
  default_http  = 80
  default_https = 443
#if MIN_VERSION_base(4,13,0)
failHTTPS :: MonadFail m => URI -> m ()
#else
failHTTPS :: Monad m => URI -> m ()
#endif
failHTTPS uri
  | map toLower (uriScheme uri) == "https:" = fail "https not supported"
  | otherwise = return ()
reqURIAuth :: Request ty -> URIAuth
reqURIAuth req =
  case uriAuthority (rqURI req) of
    Just ua -> ua
    _ -> case lookupHeader HdrHost (rqHeaders req) of
           Nothing -> error ("reqURIAuth: no URI authority for: " ++ show req)
           Just h  ->
              case toHostPort h of
                (ht,p) -> URIAuth { uriUserInfo = ""
                                  , uriRegName  = ht
                                  , uriPort     = p
                                  }
  where
    
    
   toHostPort h = break (==':') h
httpVersion :: String
httpVersion = "HTTP/1.1"
data RequestMethod = HEAD | PUT | GET | POST | DELETE | OPTIONS | TRACE | CONNECT | Custom String
    deriving(Eq)
instance Show RequestMethod where
  show x =
    case x of
      HEAD     -> "HEAD"
      PUT      -> "PUT"
      GET      -> "GET"
      POST     -> "POST"
      DELETE   -> "DELETE"
      OPTIONS  -> "OPTIONS"
      TRACE    -> "TRACE"
      CONNECT  -> "CONNECT"
      Custom c -> c
rqMethodMap :: [(String, RequestMethod)]
rqMethodMap = [("HEAD",    HEAD),
               ("PUT",     PUT),
               ("GET",     GET),
               ("POST",    POST),
               ("DELETE",  DELETE),
               ("OPTIONS", OPTIONS),
               ("TRACE",   TRACE),
               ("CONNECT", CONNECT)]
type Request_String  = Request String
type Response_String = Response String
type HTTPRequest a  = Request  a
type HTTPResponse a = Response a
data Request a =
     Request { rqURI       :: URI   
                                    
                                    
                                    
                                    
             , rqMethod    :: RequestMethod
             , rqHeaders   :: [Header]
             , rqBody      :: a
             }
instance Show (Request a) where
    show req@(Request u m h _) =
        show m ++ sp ++ alt_uri ++ sp ++ ver ++ crlf
        ++ foldr (++) [] (map show (dropHttpVersion h)) ++ crlf
        where
            ver = fromMaybe httpVersion (getRequestVersion req)
            alt_uri = show $ if null (uriPath u) || head (uriPath u) /= '/'
                        then u { uriPath = '/' : uriPath u }
                        else u
instance HasHeaders (Request a) where
    getHeaders = rqHeaders
    setHeaders rq hdrs = rq { rqHeaders=hdrs }
type ResponseCode  = (Int,Int,Int)
type ResponseData  = (ResponseCode,String,[Header])
type RequestData   = (RequestMethod,URI,[Header])
data Response a =
    Response { rspCode     :: ResponseCode
             , rspReason   :: String
             , rspHeaders  :: [Header]
             , rspBody     :: a
             }
instance Show (Response a) where
    show rsp@(Response (a,b,c) reason headers _) =
        ver ++ ' ' : map intToDigit [a,b,c] ++ ' ' : reason ++ crlf
        ++ foldr (++) [] (map show (dropHttpVersion headers)) ++ crlf
     where
      ver = fromMaybe httpVersion (getResponseVersion rsp)
instance HasHeaders (Response a) where
    getHeaders = rspHeaders
    setHeaders rsp hdrs = rsp { rspHeaders=hdrs }
libUA :: String
libUA = "hs-HTTP-4000.0.9"
{-# DEPRECATED libUA "Use defaultUserAgent instead (but note the user agent name change)" #-}
defaultUserAgent :: String
defaultUserAgent = "haskell-HTTP/" ++ httpPackageVersion
httpPackageVersion :: String
httpPackageVersion = showVersion Self.version
defaultGETRequest :: URI -> Request_String
defaultGETRequest uri = defaultGETRequest_ uri
defaultGETRequest_ :: BufferType a => URI -> Request a
defaultGETRequest_ uri = mkRequest GET uri
mkRequest :: BufferType ty => RequestMethod -> URI -> Request ty
mkRequest meth uri = req
 where
  req =
    Request { rqURI      = uri
            , rqBody     = empty
            , rqHeaders  = [ Header HdrContentLength "0"
                           , Header HdrUserAgent     defaultUserAgent
                           ]
            , rqMethod   = meth
            }
  empty = buf_empty (toBufOps req)
setRequestBody :: Request_String -> (String, String) -> Request_String
setRequestBody req (typ, body) = req' { rqBody=body }
  where
    req' = replaceHeader HdrContentType typ .
           replaceHeader HdrContentLength (show $ length body) $
           req
toBufOps :: BufferType a => Request a -> BufferOp a
toBufOps _ = bufferOps
parseRequestHead :: [String] -> Result RequestData
parseRequestHead         [] = Left ErrorClosed
parseRequestHead (com:hdrs) = do
  (version,rqm,uri) <- requestCommand com (words com)
  hdrs'              <- parseHeaders hdrs
  return (rqm,uri,withVer version hdrs')
 where
  withVer [] hs = hs
  withVer (h:_) hs = withVersion h hs
  requestCommand l _yes@(rqm:uri:version) =
    case (parseURIReference uri, lookup rqm rqMethodMap) of
     (Just u, Just r) -> return (version,r,u)
     (Just u, Nothing) -> return (version,Custom rqm,u)
     _                -> parse_err l
  requestCommand l _
   | null l    = failWith ErrorClosed
   | otherwise = parse_err l
  parse_err l = responseParseError "parseRequestHead"
                   ("Request command line parse failure: " ++ l)
parseResponseHead :: [String] -> Result ResponseData
parseResponseHead []         = failWith ErrorClosed
parseResponseHead (sts:hdrs) = do
  (version,code,reason)  <- responseStatus sts (words sts)
  hdrs'                  <- parseHeaders hdrs
  return (code,reason, withVersion version hdrs')
 where
  responseStatus _l _yes@(version:code:reason) =
    return (version,match code,concatMap (++" ") reason)
  responseStatus l _no
    | null l    = failWith ErrorClosed  
    | otherwise = parse_err l
  parse_err l =
    responseParseError
        "parseResponseHead"
        ("Response status line parse failure: " ++ l)
  match [a,b,c] = (digitToInt a,
                   digitToInt b,
                   digitToInt c)
  match _ = (-1,-1,-1)  
withVersion :: String -> [Header] -> [Header]
withVersion v hs
 | v == httpVersion = hs  
 | otherwise        = (Header (HdrCustom "X-HTTP-Version") v) : hs
getRequestVersion :: Request a -> Maybe String
getRequestVersion r = getHttpVersion r
setRequestVersion :: String -> Request a -> Request a
setRequestVersion s r = setHttpVersion r s
getResponseVersion :: Response a -> Maybe String
getResponseVersion r = getHttpVersion r
setResponseVersion :: String -> Response a -> Response a
setResponseVersion s r = setHttpVersion r s
getHttpVersion :: HasHeaders a => a -> Maybe String
getHttpVersion r =
  fmap toVersion      $
   find isHttpVersion $
    getHeaders r
 where
  toVersion (Header _ x) = x
setHttpVersion :: HasHeaders a => a -> String -> a
setHttpVersion r v =
  setHeaders r $
   withVersion v  $
    dropHttpVersion $
     getHeaders r
dropHttpVersion :: [Header] -> [Header]
dropHttpVersion hs = filter (not.isHttpVersion) hs
isHttpVersion :: Header -> Bool
isHttpVersion (Header (HdrCustom "X-HTTP-Version") _) = True
isHttpVersion _ = False
data ResponseNextStep
 = Continue
 | Retry
 | Done
 | ExpectEntity
 | DieHorribly String
matchResponse :: RequestMethod -> ResponseCode -> ResponseNextStep
matchResponse rqst rsp =
    case rsp of
        (1,0,0) -> Continue
        (1,0,1) -> Done        
        (1,_,_) -> Continue    
        (2,0,4) -> Done
        (2,0,5) -> Done
        (2,_,_) -> ans
        (3,0,4) -> Done
        (3,0,5) -> Done
        (3,_,_) -> ans
        (4,1,7) -> Retry       
        (4,_,_) -> ans
        (5,_,_) -> ans
        (a,b,c) -> DieHorribly ("Response code " ++ map intToDigit [a,b,c] ++ " not recognised")
    where
        ans | rqst == HEAD = Done
            | otherwise    = ExpectEntity
replacement_character :: Char
replacement_character = '\xfffd'
encodeChar :: Char -> [Word8]
encodeChar = map fromIntegral . go . ord
 where
  go oc
   | oc <= 0x7f       = [oc]
   | oc <= 0x7ff      = [ 0xc0 + (oc `shiftR` 6)
                        , 0x80 + oc .&. 0x3f
                        ]
   | oc <= 0xffff     = [ 0xe0 + (oc `shiftR` 12)
                        , 0x80 + ((oc `shiftR` 6) .&. 0x3f)
                        , 0x80 + oc .&. 0x3f
                        ]
   | otherwise        = [ 0xf0 + (oc `shiftR` 18)
                        , 0x80 + ((oc `shiftR` 12) .&. 0x3f)
                        , 0x80 + ((oc `shiftR` 6) .&. 0x3f)
                        , 0x80 + oc .&. 0x3f
                        ]
decode :: [Word8] -> String
decode [    ] = ""
decode (c:cs)
  | c < 0x80  = chr (fromEnum c) : decode cs
  | c < 0xc0  = replacement_character : decode cs
  | c < 0xe0  = multi1
  | c < 0xf0  = multi_byte 2 0xf  0x800
  | c < 0xf8  = multi_byte 3 0x7  0x10000
  | c < 0xfc  = multi_byte 4 0x3  0x200000
  | c < 0xfe  = multi_byte 5 0x1  0x4000000
  | otherwise = replacement_character : decode cs
  where
    multi1 = case cs of
      c1 : ds | c1 .&. 0xc0 == 0x80 ->
        let d = ((fromEnum c .&. 0x1f) `shiftL` 6) .|.  fromEnum (c1 .&. 0x3f)
        in if d >= 0x000080 then toEnum d : decode ds
                            else replacement_character : decode ds
      _ -> replacement_character : decode cs
    multi_byte :: Int -> Word8 -> Int -> [Char]
    multi_byte i mask overlong = aux i cs (fromEnum (c .&. mask))
      where
        aux 0 rs acc
          | overlong <= acc && acc <= 0x10ffff &&
            (acc < 0xd800 || 0xdfff < acc)     &&
            (acc < 0xfffe || 0xffff < acc)      = chr acc : decode rs
          | otherwise = replacement_character : decode rs
        aux n (r:rs) acc
          | r .&. 0xc0 == 0x80 = aux (n-1) rs
                               $ shiftL acc 6 .|. fromEnum (r .&. 0x3f)
        aux _ rs     _ = replacement_character : decode rs
urlDecode :: String -> String
urlDecode = go []
  where
    go bs ('%':a:b:rest)           = go (fromIntegral (16 * digitToInt a + digitToInt b) : bs) rest
    go bs (h:t) | fromEnum h < 256 = go (fromIntegral (fromEnum h) : bs) t 
    go [] []                       = []
    go [] (h:t)                    = h : go [] t 
    go bs rest                     = decode (reverse bs) ++ go [] rest
urlEncode :: String -> String
urlEncode     [] = []
urlEncode (ch:t)
  | (isAscii ch && isAlphaNum ch) || ch `elem` "-_.~" = ch : urlEncode t
  | not (isAscii ch) = foldr escape (urlEncode t) (encodeChar ch)
  | otherwise = escape (fromIntegral (fromEnum ch)) (urlEncode t)
    where
     escape b rs = '%':showH (b `div` 16) (showH (b `mod` 16) rs)
     showH :: Word8 -> String -> String
     showH x xs
       | x <= 9    = to (o_0 + x) : xs
       | otherwise = to (o_A + (x-10)) : xs
      where
       to  = toEnum  .  fromIntegral
       fro = fromIntegral . fromEnum
       o_0 = fro '0'
       o_A = fro 'A'
urlEncodeVars :: [(String,String)] -> String
urlEncodeVars ((n,v):t) =
    let (same,diff) = partition ((==n) . fst) t
    in urlEncode n ++ '=' : foldl (\x y -> x ++ ',' : urlEncode y) (urlEncode $ v) (map snd same)
       ++ urlEncodeRest diff
       where urlEncodeRest [] = []
             urlEncodeRest diff = '&' : urlEncodeVars diff
urlEncodeVars [] = []
#if MIN_VERSION_base(4,13,0)
getAuth :: MonadFail m => Request ty -> m URIAuthority
#else
getAuth :: Monad m => Request ty -> m URIAuthority
#endif
getAuth r =
   
  case parseURIAuthority auth of
    Just x -> return x
    Nothing -> fail $ "Network.HTTP.Base.getAuth: Error parsing URI authority '" ++ auth ++ "'"
 where
  auth = maybe (uriToAuthorityString uri) id (findHeader HdrHost r)
  uri  = rqURI r
{-# DEPRECATED normalizeRequestURI "Please use Network.HTTP.Base.normalizeRequest instead" #-}
normalizeRequestURI :: Bool -> String -> Request ty -> Request ty
normalizeRequestURI doClose h r =
  (if doClose then replaceHeader HdrConnection "close" else id) $
  insertHeaderIfMissing HdrHost h $
    r { rqURI = (rqURI r){ uriScheme = ""
                         , uriAuthority = Nothing
                         }}
data NormalizeRequestOptions ty
 = NormalizeRequestOptions
     { normDoClose   :: Bool
     , normForProxy  :: Bool
     , normUserAgent :: Maybe String
     , normCustoms   :: [RequestNormalizer ty]
     }
type RequestNormalizer ty = NormalizeRequestOptions ty -> Request ty -> Request ty
defaultNormalizeRequestOptions :: NormalizeRequestOptions ty
defaultNormalizeRequestOptions = NormalizeRequestOptions
     { normDoClose   = False
     , normForProxy  = False
     , normUserAgent = Just defaultUserAgent
     , normCustoms   = []
     }
normalizeRequest :: NormalizeRequestOptions ty
                 -> Request ty
                 -> Request ty
normalizeRequest opts req = foldr (\ f -> f opts) req normalizers
 where
  
  normalizers =
     ( normalizeHostURI
     : normalizeBasicAuth
     : normalizeConnectionClose
     : normalizeUserAgent
     : normCustoms opts
     )
normalizeUserAgent :: RequestNormalizer ty
normalizeUserAgent opts req =
  case normUserAgent opts of
    Nothing -> req
    Just ua ->
     case findHeader HdrUserAgent req of
       Just u  | u /= defaultUserAgent -> req
       _ -> replaceHeader HdrUserAgent ua req
normalizeConnectionClose :: RequestNormalizer ty
normalizeConnectionClose opts req
 | normDoClose opts = replaceHeader HdrConnection "close" req
 | otherwise        = req
normalizeBasicAuth :: RequestNormalizer ty
normalizeBasicAuth _ req =
  case getAuth req of
    Just uriauth ->
      case (user uriauth, password uriauth) of
        (Just u, Just p) ->
          insertHeaderIfMissing HdrAuthorization astr req
            where
              astr = "Basic " ++ base64encode (u ++ ":" ++ p)
              base64encode = Base64.encode . stringToOctets :: String -> String
              stringToOctets = map (fromIntegral . fromEnum) :: String -> [Word8]
        (_, _) -> req
    Nothing ->req
normalizeHostURI :: RequestNormalizer ty
normalizeHostURI opts req =
  case splitRequestURI uri of
    ("",_uri_abs)
      | forProxy ->
         case findHeader HdrHost req of
           Nothing -> req 
           Just h  -> req{rqURI=uri{ uriAuthority=Just URIAuth{uriUserInfo="", uriRegName=hst, uriPort=pNum}
                                   , uriScheme=if (null (uriScheme uri)) then "http" else uriScheme uri
                                   }}
            where
              hst = case span (/='@') user_hst of
                       (as,'@':bs) ->
                          case span (/=':') as of
                            (_,_:_) -> bs
                            _ -> user_hst
                       _ -> user_hst
              (user_hst, pNum) =
                 case span isDigit (reverse h) of
                   (ds,':':bs) -> (reverse bs, ':':reverse ds)
                   _ -> (h,"")
      | otherwise ->
         case findHeader HdrHost req of
           Nothing -> req 
           Just{}  -> req
    (h,uri_abs)
      | forProxy  -> insertHeaderIfMissing HdrHost h req
      | otherwise -> replaceHeader HdrHost h req{rqURI=uri_abs} 
 where
   uri0     = rqURI req
     
   uri      = uri0{uriAuthority=fmap (\ x -> x{uriUserInfo=""}) (uriAuthority uri0)}
   forProxy = normForProxy opts
splitRequestURI :: URI -> (String, URI)
splitRequestURI uri = (uriToAuthorityString uri, uri{uriScheme="", uriAuthority=Nothing})
{-# DEPRECATED normalizeHostHeader "Please use Network.HTTP.Base.normalizeRequest instead" #-}
normalizeHostHeader :: Request ty -> Request ty
normalizeHostHeader rq =
  insertHeaderIfMissing HdrHost
                        (uriToAuthorityString $ rqURI rq)
                        rq
findConnClose :: [Header] -> Bool
findConnClose hdrs =
  maybe False
        (\ x -> map toLower (trim x) == "close")
        (lookupHeader HdrConnection hdrs)
linearTransfer :: (Int -> IO (Result a)) -> Int -> IO (Result ([Header],a))
linearTransfer readBlk n = fmapE (\str -> Right ([],str)) (readBlk n)
hopefulTransfer :: BufferOp a
                -> IO (Result a)
                -> [a]
                -> IO (Result ([Header],a))
hopefulTransfer bufOps readL strs
    = readL >>=
      either (\v -> return $ Left v)
             (\more -> if (buf_isEmpty bufOps more)
                         then return (Right ([], buf_concat bufOps $ reverse strs))
                         else hopefulTransfer bufOps readL (more:strs))
chunkedTransfer :: BufferOp a
                -> IO (Result a)
                -> (Int -> IO (Result a))
                -> IO (Result ([Header], a))
chunkedTransfer bufOps readL readBlk = chunkedTransferC bufOps readL readBlk [] 0
chunkedTransferC :: BufferOp a
                 -> IO (Result a)
                 -> (Int -> IO (Result a))
                 -> [a]
                 -> Int
                 -> IO (Result ([Header], a))
chunkedTransferC bufOps readL readBlk acc n = do
  v <- readL
  case v of
    Left e -> return (Left e)
    Right line
     | size == 0 ->
         
        fmapE (\ strs -> do
                 ftrs <- parseHeaders (map (buf_toStr bufOps) strs)
                  
                 let ftrs' = Header HdrContentLength (show n) : ftrs
                 return (ftrs',buf_concat bufOps (reverse acc)))
              (readTillEmpty2 bufOps readL [])
     | otherwise -> do
         some <- readBlk size
         case some of
           Left e -> return (Left e)
           Right cdata -> do
               _ <- readL 
               chunkedTransferC bufOps readL readBlk (cdata:acc) (n+size)
     where
      size
       | buf_isEmpty bufOps line = 0
       | otherwise =
         case readHex (buf_toStr bufOps line) of
          (hx,_):_ -> hx
          _        -> 0
uglyDeathTransfer :: String -> IO (Result ([Header],a))
uglyDeathTransfer loc = return (responseParseError loc "Unknown Transfer-Encoding")
readTillEmpty1 :: BufferOp a
               -> IO (Result a)
               -> IO (Result [a])
readTillEmpty1 bufOps readL =
  readL >>=
    either (return . Left)
           (\ s ->
               if buf_isLineTerm bufOps s
                then readTillEmpty1 bufOps readL
                else readTillEmpty2 bufOps readL [s])
readTillEmpty2 :: BufferOp a
               -> IO (Result a)
               -> [a]
               -> IO (Result [a])
readTillEmpty2 bufOps readL list =
    readL >>=
      either (return . Left)
             (\ s ->
                if buf_isLineTerm bufOps s || buf_isEmpty bufOps s
                 then return (Right $ reverse (s:list))
                 else readTillEmpty2 bufOps readL (s:list))
catchIO :: IO a -> (IOException -> IO a) -> IO a
catchIO a h = Exception.catch a h
catchIO_ :: IO a -> IO a -> IO a
catchIO_ a h = Exception.catch a (\(_ :: IOException) -> h)
responseParseError :: String -> String -> Result a
responseParseError loc v = failWith (ErrorParse (loc ++ ' ':v))