{-# LINE 1 "dist/build/Network/Curlhs/Setopt.hsc" #-}
-------------------------------------------------------------------------------
{-# LINE 2 "dist/build/Network/Curlhs/Setopt.hsc" #-}
-- |
-- Module      :  Network.Curlhs.Setopt
-- Copyright   :  Copyright © 2012 Krzysztof Kardzis
-- License     :  ISC License (MIT/BSD-style, see LICENSE file for details)
-- 
-- Maintainer  :  Krzysztof Kardzis <kkardzis@gmail.com>
-- Stability   :  experimental
-- Portability :  non-portable
--
-------------------------------------------------------------------------------

module Network.Curlhs.Setopt
  ( curl_easy_setopt
  , freeCallbacks
  ) where

import Foreign.Marshal.Utils (copyBytes, fromBool)
import Foreign.C.Types       (CLong)
import Foreign.Ptr           (FunPtr, nullFunPtr, freeHaskellFunPtr)

import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds)
import Data.Time.Clock       (UTCTime)
import Data.Bits             ((.|.))
import Data.List             (foldl')
import Data.IORef            (IORef, atomicModifyIORef)

import qualified Data.ByteString as BS
import Data.ByteString.Unsafe (unsafeUseAsCStringLen)
import Data.ByteString        (ByteString, useAsCString, packCStringLen)

import Network.Curlhs.Errors
import Network.Curlhs.Types
import Network.Curlhs.Base


-------------------------------------------------------------------------------
freeCallbacks :: CURL -> IO ()
freeCallbacks curl = do
  keepCallback (cb_write curl) Nothing
  keepCallback (cb_read  curl) Nothing

keepCallback :: IORef (Maybe (FunPtr a)) -> Maybe (FunPtr a) -> IO ()
keepCallback r mf =
  atomicModifyIORef r (\v -> (mf, v)) >>= maybe (return ()) freeHaskellFunPtr

makeCallback :: Maybe cb -> IORef (Maybe (FunPtr a))
             -> (FunPtr a -> IO CCURLcode) -> (cb -> IO (FunPtr a)) -> IO ()
makeCallback (Just cb) ref setcb wrapcb = withCODE $ do
  fptr <- wrapcb cb
  code <- setcb fptr
  if (code == cCURLE_OK)
    then keepCallback ref (Just fptr)
    else freeHaskellFunPtr fptr
  return code
makeCallback Nothing ref setcb _ = withCODE $ do
  code <- setcb nullFunPtr
  keepCallback ref Nothing
  return code


-------------------------------------------------------------------------------

{-# LINE 64 "dist/build/Network/Curlhs/Setopt.hsc" #-}

-------------------------------------------------------------------------------
-- | Set options for a curl easy handle
--   (<http://curl.haxx.se/libcurl/c/curl_easy_setopt.html>).
-------------------------------------------------------------------------------
curl_easy_setopt :: CURL -> [CURLoption] -> IO ()
curl_easy_setopt curl opts = flip mapM_ opts $ \opt -> case opt of

  ---- CALLBACK OPTIONS -------------------------------------------------------
  CURLOPT_WRITEFUNCTION f -> so'FWRITE curl f
  CURLOPT_READFUNCTION  f -> so'FREAD  curl f

  ---- BEHAVIOR OPTIONS -------------------------------------------------------
  CURLOPT_VERBOSE x -> bool cCURLOPT_VERBOSE x
{-# LINE 78 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_HEADER x -> bool cCURLOPT_HEADER x
{-# LINE 79 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_NOPROGRESS x -> bool cCURLOPT_NOPROGRESS x
{-# LINE 80 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_NOSIGNAL x -> bool cCURLOPT_NOSIGNAL x
{-# LINE 81 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_WILDCARDMATCH x -> bool cCURLOPT_WILDCARDMATCH x
{-# LINE 82 "dist/build/Network/Curlhs/Setopt.hsc" #-}

  ---- ERROR OPTIONS ----------------------------------------------------------
  -- CURLOPT_ERRORBUFFER
  -- CURLOPT_STDERR
  CURLOPT_FAILONERROR x -> bool cCURLOPT_FAILONERROR x
{-# LINE 87 "dist/build/Network/Curlhs/Setopt.hsc" #-}

  ---- NETWORK OPTIONS --------------------------------------------------------
  CURLOPT_URL x -> string cCURLOPT_URL x
{-# LINE 90 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_PROTOCOLS x -> enum cCURLOPT_PROTOCOLS x
{-# LINE 91 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_REDIR_PROTOCOLS x -> enum cCURLOPT_REDIR_PROTOCOLS x
{-# LINE 92 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_PROXY x -> string cCURLOPT_PROXY x
{-# LINE 93 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_PROXYPORT x -> int cCURLOPT_PROXYPORT x
{-# LINE 94 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_PROXYTYPE x -> enum cCURLOPT_PROXYTYPE x
{-# LINE 95 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_NOPROXY x -> string cCURLOPT_NOPROXY x
{-# LINE 96 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_HTTPPROXYTUNNEL x -> bool cCURLOPT_HTTPPROXYTUNNEL x
{-# LINE 97 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SOCKS5_GSSAPI_SERVICE x -> string cCURLOPT_SOCKS5_GSSAPI_SERVICE x
{-# LINE 98 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SOCKS5_GSSAPI_NEC x -> bool cCURLOPT_SOCKS5_GSSAPI_NEC x
{-# LINE 99 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_INTERFACE x -> string cCURLOPT_INTERFACE x
{-# LINE 100 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_LOCALPORT x -> int cCURLOPT_LOCALPORT x
{-# LINE 101 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_LOCALPORTRANGE x -> int cCURLOPT_LOCALPORTRANGE x
{-# LINE 102 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_DNS_CACHE_TIMEOUT x -> int cCURLOPT_DNS_CACHE_TIMEOUT x
{-# LINE 103 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_DNS_USE_GLOBAL_CACHE x -> bool cCURLOPT_DNS_USE_GLOBAL_CACHE x
{-# LINE 104 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_BUFFERSIZE x -> int cCURLOPT_BUFFERSIZE x
{-# LINE 105 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_PORT x -> int cCURLOPT_PORT x
{-# LINE 106 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_TCP_NODELAY x -> bool cCURLOPT_TCP_NODELAY x
{-# LINE 107 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_ADDRESS_SCOPE x -> int cCURLOPT_ADDRESS_SCOPE x
{-# LINE 108 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_TCP_KEEPALIVE x -> bool cCURLOPT_TCP_KEEPALIVE x
{-# LINE 109 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_TCP_KEEPIDLE x -> int cCURLOPT_TCP_KEEPIDLE x
{-# LINE 110 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_TCP_KEEPINTVL x -> int cCURLOPT_TCP_KEEPINTVL x
{-# LINE 111 "dist/build/Network/Curlhs/Setopt.hsc" #-}

  ---- NAMES and PASSWORDS OPTIONS (Authentication) ---------------------------
  CURLOPT_NETRC x -> enum cCURLOPT_NETRC x
{-# LINE 114 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_NETRC_FILE x -> string cCURLOPT_NETRC_FILE x
{-# LINE 115 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_USERPWD x -> string cCURLOPT_USERPWD x
{-# LINE 116 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_PROXYUSERPWD x -> string cCURLOPT_PROXYUSERPWD x
{-# LINE 117 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_USERNAME x -> string cCURLOPT_USERNAME x
{-# LINE 118 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_PASSWORD x -> string cCURLOPT_PASSWORD x
{-# LINE 119 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_PROXYUSERNAME x -> string cCURLOPT_PROXYUSERNAME x
{-# LINE 120 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_PROXYPASSWORD x -> string cCURLOPT_PROXYPASSWORD x
{-# LINE 121 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_HTTPAUTH x -> enum cCURLOPT_HTTPAUTH x
{-# LINE 122 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_TLSAUTH_TYPE x -> string cCURLOPT_TLSAUTH_TYPE x
{-# LINE 123 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_TLSAUTH_USERNAME x -> string cCURLOPT_TLSAUTH_USERNAME x
{-# LINE 124 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_TLSAUTH_PASSWORD x -> string cCURLOPT_TLSAUTH_PASSWORD x
{-# LINE 125 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_PROXYAUTH x -> enum cCURLOPT_PROXYAUTH x
{-# LINE 126 "dist/build/Network/Curlhs/Setopt.hsc" #-}

  ---- HTTP OPTIONS -----------------------------------------------------------
  CURLOPT_AUTOREFERER x -> bool cCURLOPT_AUTOREFERER x
{-# LINE 129 "dist/build/Network/Curlhs/Setopt.hsc" #-}
--   #{setopt CURLOPT_ENCODING               , string   } |----:7215|
  CURLOPT_ACCEPT_ENCODING x -> string cCURLOPT_ACCEPT_ENCODING x
{-# LINE 131 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_TRANSFER_ENCODING x -> bool cCURLOPT_TRANSFER_ENCODING x
{-# LINE 132 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_FOLLOWLOCATION x -> bool cCURLOPT_FOLLOWLOCATION x
{-# LINE 133 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_UNRESTRICTED_AUTH x -> bool cCURLOPT_UNRESTRICTED_AUTH x
{-# LINE 134 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_MAXREDIRS x -> int cCURLOPT_MAXREDIRS x
{-# LINE 135 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_POSTREDIR x -> enum cCURLOPT_POSTREDIR x
{-# LINE 136 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_PUT x -> bool cCURLOPT_PUT x
{-# LINE 137 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_POST x -> bool cCURLOPT_POST x
{-# LINE 138 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  -- #{setopt CURLOPT_POSTFIELDS             , buffer   }
  CURLOPT_POSTFIELDSIZE x -> int cCURLOPT_POSTFIELDSIZE x
{-# LINE 140 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_POSTFIELDSIZE_LARGE x -> int64 cCURLOPT_POSTFIELDSIZE_LARGE x
{-# LINE 141 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_COPYPOSTFIELDS x -> string cCURLOPT_COPYPOSTFIELDS x
{-# LINE 142 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  -- CURLOPT_HTTPPOST
  CURLOPT_REFERER x -> string cCURLOPT_REFERER x
{-# LINE 144 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_USERAGENT x -> string cCURLOPT_USERAGENT x
{-# LINE 145 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  -- #{setopt CURLOPT_HTTPHEADER             , slist    }
  -- #{setopt CURLOPT_HTTP200ALIASES         , slist    }
  CURLOPT_COOKIE x -> string cCURLOPT_COOKIE x
{-# LINE 148 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_COOKIEFILE x -> string cCURLOPT_COOKIEFILE x
{-# LINE 149 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_COOKIEJAR x -> string cCURLOPT_COOKIEJAR x
{-# LINE 150 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_COOKIESESSION x -> bool cCURLOPT_COOKIESESSION x
{-# LINE 151 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_COOKIELIST x -> string cCURLOPT_COOKIELIST x
{-# LINE 152 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_HTTPGET x -> bool cCURLOPT_HTTPGET x
{-# LINE 153 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_HTTP_VERSION x -> enum cCURLOPT_HTTP_VERSION x
{-# LINE 154 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_IGNORE_CONTENT_LENGTH x -> bool cCURLOPT_IGNORE_CONTENT_LENGTH x
{-# LINE 155 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_HTTP_CONTENT_DECODING x -> bool cCURLOPT_HTTP_CONTENT_DECODING x
{-# LINE 156 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_HTTP_TRANSFER_DECODING x -> bool cCURLOPT_HTTP_TRANSFER_DECODING x
{-# LINE 157 "dist/build/Network/Curlhs/Setopt.hsc" #-}

  ---- SMTP OPTIONS -----------------------------------------------------------
  CURLOPT_MAIL_FROM x -> string cCURLOPT_MAIL_FROM x
{-# LINE 160 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  -- #{setopt CURLOPT_MAIL_RCTP              , slist    }
  CURLOPT_MAIL_AUTH x -> string cCURLOPT_MAIL_AUTH x
{-# LINE 162 "dist/build/Network/Curlhs/Setopt.hsc" #-}

  ---- TFTP OPTIONS -----------------------------------------------------------
  CURLOPT_TFTP_BLKSIZE x -> int cCURLOPT_TFTP_BLKSIZE x
{-# LINE 165 "dist/build/Network/Curlhs/Setopt.hsc" #-}

  ---- FTP OPTIONS ------------------------------------------------------------
  CURLOPT_FTPPORT x -> string cCURLOPT_FTPPORT x
{-# LINE 168 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  -- #{setopt CURLOPT_QUOTE                  , slist    }
  -- #{setopt CURLOPT_POSTQUOTE              , slist    }
  -- #{setopt CURLOPT_PREQUOTE               , slist    }
  CURLOPT_DIRLISTONLY x -> bool cCURLOPT_DIRLISTONLY x
{-# LINE 172 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_APPEND x -> bool cCURLOPT_APPEND x
{-# LINE 173 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_FTP_USE_EPRT x -> bool cCURLOPT_FTP_USE_EPRT x
{-# LINE 174 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_FTP_USE_EPSV x -> bool cCURLOPT_FTP_USE_EPSV x
{-# LINE 175 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_FTP_USE_PRET x -> bool cCURLOPT_FTP_USE_PRET x
{-# LINE 176 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_FTP_CREATE_MISSING_DIRS x -> enum cCURLOPT_FTP_CREATE_MISSING_DIRS x
{-# LINE 177 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_FTP_RESPONSE_TIMEOUT x -> int cCURLOPT_FTP_RESPONSE_TIMEOUT x
{-# LINE 178 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_FTP_ALTERNATIVE_TO_USER x -> string cCURLOPT_FTP_ALTERNATIVE_TO_USER x
{-# LINE 179 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_FTP_SKIP_PASV_IP x -> bool cCURLOPT_FTP_SKIP_PASV_IP x
{-# LINE 180 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_FTPSSLAUTH x -> enum cCURLOPT_FTPSSLAUTH x
{-# LINE 181 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_FTP_SSL_CCC x -> enum cCURLOPT_FTP_SSL_CCC x
{-# LINE 182 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_FTP_ACCOUNT x -> string cCURLOPT_FTP_ACCOUNT x
{-# LINE 183 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_FTP_FILEMETHOD x -> enum cCURLOPT_FTP_FILEMETHOD x
{-# LINE 184 "dist/build/Network/Curlhs/Setopt.hsc" #-}

  ---- RTSP OPTIONS -----------------------------------------------------------
  CURLOPT_RTSP_REQUEST x -> enum cCURLOPT_RTSP_REQUEST x
{-# LINE 187 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_RTSP_SESSION_ID x -> string cCURLOPT_RTSP_SESSION_ID x
{-# LINE 188 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_RTSP_STREAM_URI x -> string cCURLOPT_RTSP_STREAM_URI x
{-# LINE 189 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_RTSP_TRANSPORT x -> string cCURLOPT_RTSP_TRANSPORT x
{-# LINE 190 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  -- #{setopt CURLOPT_RTSP_HEADER            , slist    }
  CURLOPT_RTSP_CLIENT_CSEQ x -> int cCURLOPT_RTSP_CLIENT_CSEQ x
{-# LINE 192 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_RTSP_SERVER_CSEQ x -> int cCURLOPT_RTSP_SERVER_CSEQ x
{-# LINE 193 "dist/build/Network/Curlhs/Setopt.hsc" #-}

  ---- PROTOCOL OPTIONS -------------------------------------------------------
  CURLOPT_TRANSFERTEXT x -> bool cCURLOPT_TRANSFERTEXT x
{-# LINE 196 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_PROXY_TRANSFER_MODE x -> bool cCURLOPT_PROXY_TRANSFER_MODE x
{-# LINE 197 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_CRLF x -> bool cCURLOPT_CRLF x
{-# LINE 198 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_RANGE x -> string cCURLOPT_RANGE x
{-# LINE 199 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_RESUME_FROM x -> int cCURLOPT_RESUME_FROM x
{-# LINE 200 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_RESUME_FROM_LARGE x -> int64 cCURLOPT_RESUME_FROM_LARGE x
{-# LINE 201 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_CUSTOMREQUEST x -> string cCURLOPT_CUSTOMREQUEST x
{-# LINE 202 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_FILETIME x -> bool cCURLOPT_FILETIME x
{-# LINE 203 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_NOBODY x -> bool cCURLOPT_NOBODY x
{-# LINE 204 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_INFILESIZE x -> int cCURLOPT_INFILESIZE x
{-# LINE 205 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_INFILESIZE_LARGE x -> int64 cCURLOPT_INFILESIZE_LARGE x
{-# LINE 206 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_UPLOAD x -> bool cCURLOPT_UPLOAD x
{-# LINE 207 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_MAXFILESIZE x -> int cCURLOPT_MAXFILESIZE x
{-# LINE 208 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_MAXFILESIZE_LARGE x -> int64 cCURLOPT_MAXFILESIZE_LARGE x
{-# LINE 209 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_TIMECONDITION x -> enum cCURLOPT_TIMECONDITION x
{-# LINE 210 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_TIMEVALUE x -> time cCURLOPT_TIMEVALUE x
{-# LINE 211 "dist/build/Network/Curlhs/Setopt.hsc" #-}

  ---- CONNECTION OPTIONS -----------------------------------------------------
  CURLOPT_TIMEOUT x -> int cCURLOPT_TIMEOUT x
{-# LINE 214 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_TIMEOUT_MS x -> int cCURLOPT_TIMEOUT_MS x
{-# LINE 215 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_LOW_SPEED_LIMIT x -> int cCURLOPT_LOW_SPEED_LIMIT x
{-# LINE 216 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_LOW_SPEED_TIME x -> int cCURLOPT_LOW_SPEED_TIME x
{-# LINE 217 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_MAX_SEND_SPEED_LARGE x -> int64 cCURLOPT_MAX_SEND_SPEED_LARGE x
{-# LINE 218 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_MAX_RECV_SPEED_LARGE x -> int64 cCURLOPT_MAX_RECV_SPEED_LARGE x
{-# LINE 219 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_MAXCONNECTS x -> int cCURLOPT_MAXCONNECTS x
{-# LINE 220 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_CLOSEPOLICY x -> enum cCURLOPT_CLOSEPOLICY x
{-# LINE 221 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_FRESH_CONNECT x -> bool cCURLOPT_FRESH_CONNECT x
{-# LINE 222 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_FORBID_REUSE x -> bool cCURLOPT_FORBID_REUSE x
{-# LINE 223 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_CONNECTTIMEOUT x -> int cCURLOPT_CONNECTTIMEOUT x
{-# LINE 224 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_CONNECTTIMEOUT_MS x -> int cCURLOPT_CONNECTTIMEOUT_MS x
{-# LINE 225 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_IPRESOLVE x -> enum cCURLOPT_IPRESOLVE x
{-# LINE 226 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_CONNECT_ONLY x -> bool cCURLOPT_CONNECT_ONLY x
{-# LINE 227 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_USE_SSL x -> enum cCURLOPT_USE_SSL x
{-# LINE 228 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  -- #{setopt CURLOPT_RESOLVE                , slist    }
  CURLOPT_DNS_SERVERS x -> string cCURLOPT_DNS_SERVERS x
{-# LINE 230 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_ACCEPTTIMEOUT_MS x -> int cCURLOPT_ACCEPTTIMEOUT_MS x
{-# LINE 231 "dist/build/Network/Curlhs/Setopt.hsc" #-}

  ---- SSL and SECURITY OPTIONS -----------------------------------------------
  CURLOPT_SSLCERT x -> string cCURLOPT_SSLCERT x
{-# LINE 234 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SSLCERTTYPE x -> string cCURLOPT_SSLCERTTYPE x
{-# LINE 235 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SSLKEY x -> string cCURLOPT_SSLKEY x
{-# LINE 236 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SSLKEYTYPE x -> string cCURLOPT_SSLKEYTYPE x
{-# LINE 237 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_KEYPASSWD x -> string cCURLOPT_KEYPASSWD x
{-# LINE 238 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SSLENGINE x -> string cCURLOPT_SSLENGINE x
{-# LINE 239 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SSLENGINE_DEFAULT x -> bool cCURLOPT_SSLENGINE_DEFAULT x
{-# LINE 240 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SSLVERSION x -> enum cCURLOPT_SSLVERSION x
{-# LINE 241 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SSL_VERIFYPEER x -> bool cCURLOPT_SSL_VERIFYPEER x
{-# LINE 242 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_CAINFO x -> string cCURLOPT_CAINFO x
{-# LINE 243 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_ISSUERCERT x -> string cCURLOPT_ISSUERCERT x
{-# LINE 244 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_CAPATH x -> string cCURLOPT_CAPATH x
{-# LINE 245 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_CRLFILE x -> string cCURLOPT_CRLFILE x
{-# LINE 246 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SSL_VERIFYHOST x -> int cCURLOPT_SSL_VERIFYHOST x
{-# LINE 247 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_CERTINFO x -> bool cCURLOPT_CERTINFO x
{-# LINE 248 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_RANDOM_FILE x -> string cCURLOPT_RANDOM_FILE x
{-# LINE 249 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_EGDSOCKET x -> string cCURLOPT_EGDSOCKET x
{-# LINE 250 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SSL_CIPHER_LIST x -> string cCURLOPT_SSL_CIPHER_LIST x
{-# LINE 251 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SSL_SESSIONID_CACHE x -> bool cCURLOPT_SSL_SESSIONID_CACHE x
{-# LINE 252 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SSL_OPTIONS x -> enum cCURLOPT_SSL_OPTIONS x
{-# LINE 253 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_KRBLEVEL x -> string cCURLOPT_KRBLEVEL x
{-# LINE 254 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_GSSAPI_DELEGATION x -> enum cCURLOPT_GSSAPI_DELEGATION x
{-# LINE 255 "dist/build/Network/Curlhs/Setopt.hsc" #-}

  ---- SSH OPTIONS ------------------------------------------------------------
  CURLOPT_SSH_AUTH_TYPES x -> enum cCURLOPT_SSH_AUTH_TYPES x
{-# LINE 258 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SSH_HOST_PUBLIC_KEY_MD5 x -> string cCURLOPT_SSH_HOST_PUBLIC_KEY_MD5 x
{-# LINE 259 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SSH_PUBLIC_KEYFILE x -> string cCURLOPT_SSH_PUBLIC_KEYFILE x
{-# LINE 260 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SSH_PRIVATE_KEYFILE x -> string cCURLOPT_SSH_PRIVATE_KEYFILE x
{-# LINE 261 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_SSH_KNOWNHOSTS x -> string cCURLOPT_SSH_KNOWNHOSTS x
{-# LINE 262 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  -- CURLOPT_SSH_KEYFUNCTION
  -- CURLOPT_SSH_KEYDATA

  ---- OTHER OPTIONS ----------------------------------------------------------
  -- CURLOPT_PRIVATE
  -- CURLOPT_SHARE
  CURLOPT_NEW_FILE_PERMS x -> int cCURLOPT_NEW_FILE_PERMS x
{-# LINE 269 "dist/build/Network/Curlhs/Setopt.hsc" #-}
  CURLOPT_NEW_DIRECTORY_PERMS x -> int cCURLOPT_NEW_DIRECTORY_PERMS x
{-# LINE 270 "dist/build/Network/Curlhs/Setopt.hsc" #-}

  ---- TELNET OPTIONS ---------------------------------------------------------
  -- #{setopt CURLOPT_TELNETOPTIONS          , slist    }

  -----------------------------------------------------------------------------
  where
    string copt s = setopt'CString curl copt s
    int64  copt x = setopt'Int64   curl copt (fromIntegral   x)
    int    copt x = setopt'CLong   curl copt (fromIntegral   x)
    bool   copt x = setopt'CLong   curl copt (fromBool       x)
    time   copt x = setopt'CLong   curl copt (fromUTCTime    x)
    enum   copt x = setopt'CLong   curl copt (fromCURLenum   x)



-------------------------------------------------------------------------------
setopt'CString :: CURL -> CCURLoption'CString -> ByteString -> IO ()
setopt'CString curl copt val = useAsCString val $ \ptr ->
  withCODE $ ccurl_easy_setopt'CString (ccurlptr curl) copt ptr

setopt'Int64 :: CURL -> CCURLoption'Int64 -> CCURL_off_t -> IO ()
setopt'Int64 curl copt cval =
  withCODE $ ccurl_easy_setopt'Int64 (ccurlptr curl) copt cval

setopt'CLong :: CURL -> CCURLoption'CLong -> CLong -> IO ()
setopt'CLong curl copt cval =
  withCODE $ ccurl_easy_setopt'CLong (ccurlptr curl) copt cval


-------------------------------------------------------------------------------
so'FWRITE :: CURL -> Maybe CURL_write_callback -> IO ()
so'FWRITE curl mcb = makeCallback mcb (cb_write curl)
  (ccurl_easy_setopt'FWRITE (ccurlptr curl))
  (\cb -> wrap_ccurl_write_callback (write_callback cb))

write_callback :: CURL_write_callback -> CCURL_write_callback
write_callback fwrite ptr size nmemb _ = do
  stat <- packCStringLen (ptr, fromIntegral (size * nmemb)) >>= fwrite
  return $ case stat of
    CURL_WRITEFUNC_OK    -> (size * nmemb)
    CURL_WRITEFUNC_FAIL  -> 0
    CURL_WRITEFUNC_PAUSE -> cCURL_WRITEFUNC_PAUSE


-------------------------------------------------------------------------------
so'FREAD :: CURL -> Maybe CURL_read_callback -> IO ()
so'FREAD curl mcb = makeCallback mcb (cb_read curl)
  (ccurl_easy_setopt'FREAD (ccurlptr curl))
  (\cb -> wrap_ccurl_read_callback (read_callback cb))

read_callback :: CURL_read_callback -> CCURL_read_callback
read_callback fread buff size nmemb _ = do
  let buffLen = fromIntegral (size * nmemb)
  stat <- fread buffLen
  case stat of
    CURL_READFUNC_PAUSE -> return cCURL_READFUNC_PAUSE
    CURL_READFUNC_ABORT -> return cCURL_READFUNC_ABORT
    CURL_READFUNC_OK bs -> unsafeUseAsCStringLen (BS.take buffLen bs)
      (\(cs, cl) -> copyBytes buff cs cl >> return (fromIntegral cl))


-------------------------------------------------------------------------------
fromUTCTime :: UTCTime -> CLong
fromUTCTime = truncate . utcTimeToPOSIXSeconds


-------------------------------------------------------------------------------

{-# LINE 338 "dist/build/Network/Curlhs/Setopt.hsc" #-}

class CURLenum a where
  fromCURLenum :: a -> CLong

instance CURLenum a => CURLenum [a] where
  fromCURLenum xs = foldl' (.|.) 0 $ map fromCURLenum xs

instance CURLenum CURLproto where
  fromCURLenum x = case x of
    CURLPROTO_ALL -> cCURLPROTO_ALL
{-# LINE 348 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_HTTP -> cCURLPROTO_HTTP
{-# LINE 349 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_HTTPS -> cCURLPROTO_HTTPS
{-# LINE 350 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_FTP -> cCURLPROTO_FTP
{-# LINE 351 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_FTPS -> cCURLPROTO_FTPS
{-# LINE 352 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_SCP -> cCURLPROTO_SCP
{-# LINE 353 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_SFTP -> cCURLPROTO_SFTP
{-# LINE 354 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_TELNET -> cCURLPROTO_TELNET
{-# LINE 355 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_LDAP -> cCURLPROTO_LDAP
{-# LINE 356 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_LDAPS -> cCURLPROTO_LDAPS
{-# LINE 357 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_DICT -> cCURLPROTO_DICT
{-# LINE 358 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_FILE -> cCURLPROTO_FILE
{-# LINE 359 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_TFTP -> cCURLPROTO_TFTP
{-# LINE 360 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_IMAP -> cCURLPROTO_IMAP
{-# LINE 361 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_IMAPS -> cCURLPROTO_IMAPS
{-# LINE 362 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_POP3 -> cCURLPROTO_POP3
{-# LINE 363 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_POP3S -> cCURLPROTO_POP3S
{-# LINE 364 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_SMTP -> cCURLPROTO_SMTP
{-# LINE 365 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_SMTPS -> cCURLPROTO_SMTPS
{-# LINE 366 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_RTSP -> cCURLPROTO_RTSP
{-# LINE 367 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_RTMP -> cCURLPROTO_RTMP
{-# LINE 368 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_RTMPT -> cCURLPROTO_RTMPT
{-# LINE 369 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_RTMPE -> cCURLPROTO_RTMPE
{-# LINE 370 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_RTMPTE -> cCURLPROTO_RTMPTE
{-# LINE 371 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_RTMPS -> cCURLPROTO_RTMPS
{-# LINE 372 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_RTMPTS -> cCURLPROTO_RTMPTS
{-# LINE 373 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROTO_GOPHER -> cCURLPROTO_GOPHER
{-# LINE 374 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLproxy where
  fromCURLenum x = case x of
    CURLPROXY_HTTP -> cCURLPROXY_HTTP
{-# LINE 378 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROXY_HTTP_1_0 -> cCURLPROXY_HTTP_1_0
{-# LINE 379 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROXY_SOCKS4 -> cCURLPROXY_SOCKS4
{-# LINE 380 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROXY_SOCKS5 -> cCURLPROXY_SOCKS5
{-# LINE 381 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROXY_SOCKS4A -> cCURLPROXY_SOCKS4A
{-# LINE 382 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLPROXY_SOCKS5_HOSTNAME -> cCURLPROXY_SOCKS5_HOSTNAME
{-# LINE 383 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLnetrc where
  fromCURLenum x = case x of
    CURL_NETRC_IGNORED -> cCURL_NETRC_IGNORED
{-# LINE 387 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_NETRC_OPTIONAL -> cCURL_NETRC_OPTIONAL
{-# LINE 388 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_NETRC_REQUIRED -> cCURL_NETRC_REQUIRED
{-# LINE 389 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLauth where
  fromCURLenum x = case x of
    CURLAUTH_BASIC -> cCURLAUTH_BASIC
{-# LINE 393 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLAUTH_DIGEST -> cCURLAUTH_DIGEST
{-# LINE 394 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLAUTH_DIGEST_IE -> cCURLAUTH_DIGEST_IE
{-# LINE 395 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLAUTH_GSSNEGOTIATE -> cCURLAUTH_GSSNEGOTIATE
{-# LINE 396 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLAUTH_NTLM -> cCURLAUTH_NTLM
{-# LINE 397 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLAUTH_NTLM_WB -> cCURLAUTH_NTLM_WB
{-# LINE 398 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLAUTH_ONLY -> cCURLAUTH_ONLY
{-# LINE 399 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLAUTH_ANY -> cCURLAUTH_ANY
{-# LINE 400 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLAUTH_ANYSAFE -> cCURLAUTH_ANYSAFE
{-# LINE 401 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLtlsauth where
  fromCURLenum x = case x of
    CURL_TLSAUTH_SRP -> cCURL_TLSAUTH_SRP
{-# LINE 405 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLredir where
  fromCURLenum x = case x of
    CURL_REDIR_GET_ALL -> cCURL_REDIR_GET_ALL
{-# LINE 409 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_REDIR_POST_301 -> cCURL_REDIR_POST_301
{-# LINE 410 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_REDIR_POST_302 -> cCURL_REDIR_POST_302
{-# LINE 411 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_REDIR_POST_ALL -> cCURL_REDIR_POST_ALL
{-# LINE 412 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLhttpver where
  fromCURLenum x = case x of
    CURL_HTTP_VERSION_NONE -> cCURL_HTTP_VERSION_NONE
{-# LINE 416 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_HTTP_VERSION_1_0 -> cCURL_HTTP_VERSION_1_0
{-# LINE 417 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_HTTP_VERSION_1_1 -> cCURL_HTTP_VERSION_1_1
{-# LINE 418 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLftpcreate where
  fromCURLenum x = case x of
    CURLFTP_CREATE_DIR_NONE -> cCURLFTP_CREATE_DIR_NONE
{-# LINE 422 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLFTP_CREATE_DIR -> cCURLFTP_CREATE_DIR
{-# LINE 423 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLFTP_CREATE_DIR_RETRY -> cCURLFTP_CREATE_DIR_RETRY
{-# LINE 424 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLftpauth where
  fromCURLenum x = case x of
    CURLFTPAUTH_DEFAULT -> cCURLFTPAUTH_DEFAULT
{-# LINE 428 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLFTPAUTH_SSL -> cCURLFTPAUTH_SSL
{-# LINE 429 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLFTPAUTH_TLS -> cCURLFTPAUTH_TLS
{-# LINE 430 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLftpssl where
  fromCURLenum x = case x of
    CURLFTPSSL_CCC_NONE -> cCURLFTPSSL_CCC_NONE
{-# LINE 434 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLFTPSSL_CCC_PASSIVE -> cCURLFTPSSL_CCC_PASSIVE
{-# LINE 435 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLFTPSSL_CCC_ACTIVE -> cCURLFTPSSL_CCC_ACTIVE
{-# LINE 436 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLftpmethod where
  fromCURLenum x = case x of
    CURLFTPMETHOD_DEFAULT -> cCURLFTPMETHOD_DEFAULT
{-# LINE 440 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLFTPMETHOD_MULTICWD -> cCURLFTPMETHOD_MULTICWD
{-# LINE 441 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLFTPMETHOD_NOCWD -> cCURLFTPMETHOD_NOCWD
{-# LINE 442 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLFTPMETHOD_SINGLECWD -> cCURLFTPMETHOD_SINGLECWD
{-# LINE 443 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLrtspreq where
  fromCURLenum x = case x of
    CURL_RTSPREQ_OPTIONS -> cCURL_RTSPREQ_OPTIONS
{-# LINE 447 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_RTSPREQ_DESCRIBE -> cCURL_RTSPREQ_DESCRIBE
{-# LINE 448 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_RTSPREQ_ANNOUNCE -> cCURL_RTSPREQ_ANNOUNCE
{-# LINE 449 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_RTSPREQ_SETUP -> cCURL_RTSPREQ_SETUP
{-# LINE 450 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_RTSPREQ_PLAY -> cCURL_RTSPREQ_PLAY
{-# LINE 451 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_RTSPREQ_PAUSE -> cCURL_RTSPREQ_PAUSE
{-# LINE 452 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_RTSPREQ_TEARDOWN -> cCURL_RTSPREQ_TEARDOWN
{-# LINE 453 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_RTSPREQ_GET_PARAMETER -> cCURL_RTSPREQ_GET_PARAMETER
{-# LINE 454 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_RTSPREQ_SET_PARAMETER -> cCURL_RTSPREQ_SET_PARAMETER
{-# LINE 455 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_RTSPREQ_RECORD -> cCURL_RTSPREQ_RECORD
{-# LINE 456 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_RTSPREQ_RECEIVE -> cCURL_RTSPREQ_RECEIVE
{-# LINE 457 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLtimecond where
  fromCURLenum x = case x of
    CURL_TIMECOND_NONE -> cCURL_TIMECOND_NONE
{-# LINE 461 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_TIMECOND_IFMODSINCE -> cCURL_TIMECOND_IFMODSINCE
{-# LINE 462 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_TIMECOND_IFUNMODSINCE -> cCURL_TIMECOND_IFUNMODSINCE
{-# LINE 463 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_TIMECOND_LASTMOD -> cCURL_TIMECOND_LASTMOD
{-# LINE 464 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLclosepol where
  fromCURLenum x = case x of
    CURLCLOSEPOLICY_NONE -> cCURLCLOSEPOLICY_NONE
{-# LINE 468 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLCLOSEPOLICY_OLDEST -> cCURLCLOSEPOLICY_OLDEST
{-# LINE 469 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLCLOSEPOLICY_LEAST_RECENTLY_USED -> cCURLCLOSEPOLICY_LEAST_RECENTLY_USED
{-# LINE 470 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLCLOSEPOLICY_LEAST_TRAFFIC -> cCURLCLOSEPOLICY_LEAST_TRAFFIC
{-# LINE 471 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLCLOSEPOLICY_SLOWEST -> cCURLCLOSEPOLICY_SLOWEST
{-# LINE 472 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLCLOSEPOLICY_CALLBACK -> cCURLCLOSEPOLICY_CALLBACK
{-# LINE 473 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLipresolve where
  fromCURLenum x = case x of
    CURL_IPRESOLVE_WHATEVER -> cCURL_IPRESOLVE_WHATEVER
{-# LINE 477 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_IPRESOLVE_V4 -> cCURL_IPRESOLVE_V4
{-# LINE 478 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_IPRESOLVE_V6 -> cCURL_IPRESOLVE_V6
{-# LINE 479 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLusessl where
  fromCURLenum x = case x of
    CURLUSESSL_NONE -> cCURLUSESSL_NONE
{-# LINE 483 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLUSESSL_TRY -> cCURLUSESSL_TRY
{-# LINE 484 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLUSESSL_CONTROL -> cCURLUSESSL_CONTROL
{-# LINE 485 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLUSESSL_ALL -> cCURLUSESSL_ALL
{-# LINE 486 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLsslver where
  fromCURLenum x = case x of
    CURL_SSLVERSION_DEFAULT -> cCURL_SSLVERSION_DEFAULT
{-# LINE 490 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_SSLVERSION_TLSv1 -> cCURL_SSLVERSION_TLSv1
{-# LINE 491 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_SSLVERSION_SSLv2 -> cCURL_SSLVERSION_SSLv2
{-# LINE 492 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURL_SSLVERSION_SSLv3 -> cCURL_SSLVERSION_SSLv3
{-# LINE 493 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLsslopt where
  fromCURLenum x = case x of
    CURLSSLOPT_ALLOW_BEAST -> cCURLSSLOPT_ALLOW_BEAST
{-# LINE 497 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLgssapi where
  fromCURLenum x = case x of
    CURLGSSAPI_DELEGATION_NONE -> cCURLGSSAPI_DELEGATION_NONE
{-# LINE 501 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLGSSAPI_DELEGATION_POLICY_FLAG -> cCURLGSSAPI_DELEGATION_POLICY_FLAG
{-# LINE 502 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLGSSAPI_DELEGATION_FLAG -> cCURLGSSAPI_DELEGATION_FLAG
{-# LINE 503 "dist/build/Network/Curlhs/Setopt.hsc" #-}

instance CURLenum CURLsshauth where
  fromCURLenum x = case x of
    CURLSSH_AUTH_ANY -> cCURLSSH_AUTH_ANY
{-# LINE 507 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLSSH_AUTH_NONE -> cCURLSSH_AUTH_NONE
{-# LINE 508 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLSSH_AUTH_PUBLICKEY -> cCURLSSH_AUTH_PUBLICKEY
{-# LINE 509 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLSSH_AUTH_PASSWORD -> cCURLSSH_AUTH_PASSWORD
{-# LINE 510 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLSSH_AUTH_HOST -> cCURLSSH_AUTH_HOST
{-# LINE 511 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLSSH_AUTH_KEYBOARD -> cCURLSSH_AUTH_KEYBOARD
{-# LINE 512 "dist/build/Network/Curlhs/Setopt.hsc" #-}
    CURLSSH_AUTH_DEFAULT -> cCURLSSH_AUTH_DEFAULT
{-# LINE 513 "dist/build/Network/Curlhs/Setopt.hsc" #-}