{-# OPTIONS_GHC -optc-DCURLOPT_RTSP_HEADER=CURLOPT_RTSPHEADER #-}
{-# LINE 1 "Network/CURL000/LibHS.hsc" #-}
-------------------------------------------------------------------------------
{-# LINE 2 "Network/CURL000/LibHS.hsc" #-}
-- |
-- Module      :  Network.CURL000.LibHS
-- Copyright   :  Copyright (c) 2012-2015 Krzysztof Kardzis
-- License     :  ISC License (MIT/BSD-style, see LICENSE file for details)
--
-- Maintainer  :  Krzysztof Kardzis <kkardzis@gmail.com>
-- Stability   :  experimental
-- Portability :  non-portable
--
-------------------------------------------------------------------------------
{-# LANGUAGE GADTs #-}

module Network.CURL000.LibHS
  ( curl_easy_cleanup
 -- curl_easy_duphandle
 -- curl_easy_escape
  , curl_easy_getinfo
  , curl_easy_init
 -- curl_easy_pause
  , curl_easy_perform
  , curl_easy_recv
  , curl_easy_reset
  , curl_easy_send
  , curl_easy_setopt
 -- curl_easy_strerror
 -- curl_easy_unescape
 -- curl_escape
 -- curl_formadd
 -- curl_formfree
 -- curl_formget
 -- curl_free
 -- curl_getdate
 -- curl_getenv
  , curl_global_cleanup
  , curl_global_init
 -- curl_global_init_mem
 -- curl_maprintf
 -- curl_mfprintf
 -- curl_mprintf
 -- curl_msnprintf
 -- curl_msprintf
 -- curl_multi_add_handle
 -- curl_multi_assign
 -- curl_multi_cleanup
 -- curl_multi_fdset
 -- curl_multi_info_read
 -- curl_multi_init
 -- curl_multi_perform
 -- curl_multi_remove_handle
 -- curl_multi_setopt
 -- curl_multi_socket
 -- curl_multi_socket_action
 -- curl_multi_socket_all
 -- curl_multi_strerror
 -- curl_multi_timeout
 -- curl_multi_wait
 -- curl_mvaprintf
 -- curl_mvfprintf
 -- curl_mvprintf
 -- curl_mvsnprintf
 -- curl_mvsprintf
  , curl_share_cleanup
  , curl_share_init
  , curl_share_setopt
 -- curl_share_strerror
 -- curl_slist_append
 -- curl_slist_free_all
 -- curl_strequal
 -- curl_strnequal
 -- curl_unescape
  , curl_version
  , curl_version_info

  ) where

import qualified Network.CURL000.LibCC as C

import Network.CURL000.Types

import qualified Data.ByteString as BS
import Data.ByteString.Unsafe (unsafeUseAsCStringLen)
import Data.ByteString        (ByteString, packCStringLen)
import Data.IORef             (IORef, newIORef, atomicModifyIORef)
import Data.Time.Clock        (UTCTime)
import Data.Time.Clock.POSIX  (utcTimeToPOSIXSeconds, posixSecondsToUTCTime)
import Data.List              (partition)
import Data.Unique            (newUnique)

import Control.Applicative
import Control.Concurrent  (MVar, newMVar, takeMVar, tryPutMVar, modifyMVar)
import Control.Concurrent  (withMVar, modifyMVar_)
import Control.Exception   (throwIO, bracketOnError)
import Control.Monad       (when, forM_, foldM)

import Foreign.Marshal.Alloc
import Foreign.Marshal.Array
import Foreign.Marshal.Utils
import Foreign.Storable
import Foreign.C.String
import Foreign.C.Types
import Foreign.Ptr

import Prelude


{-# LINE 107 "Network/CURL000/LibHS.hsc" #-}


-------------------------------------------------------------------------------
-- | Global libcurl initialisation
--   (<http://curl.haxx.se/libcurl/c/curl_global_init.html>).
-------------------------------------------------------------------------------
curl_global_init :: IO ()
curl_global_init = do
  code <- C.curl_global_init 3
{-# LINE 116 "Network/CURL000/LibHS.hsc" #-}
  when (code/=0) (error "<curlhs> curl_global_init failed")


-------------------------------------------------------------------------------
-- | Global libcurl cleanup
--   (<http://curl.haxx.se/libcurl/c/curl_global_cleanup.html>).
-------------------------------------------------------------------------------
curl_global_cleanup :: IO ()
curl_global_cleanup = C.curl_global_cleanup


-------------------------------------------------------------------------------
-- | Returns the libcurl version string
--   (<http://curl.haxx.se/libcurl/c/curl_version.html>).
-------------------------------------------------------------------------------
curl_version :: IO String
curl_version = C.curl_version >>= peekCAString


-------------------------------------------------------------------------------
-- | Returns run-time libcurl version info
--   (<http://curl.haxx.se/libcurl/c/curl_version_info.html>).
-------------------------------------------------------------------------------
curl_version_info :: IO CURL_version_info
curl_version_info =
  C.curl_version_info 3 >>= \ptr -> CURL_version_info
{-# LINE 142 "Network/CURL000/LibHS.hsc" #-}
    <$> ((\hsc_ptr -> peekByteOff hsc_ptr 8) ptr >>= peekCAString)
{-# LINE 143 "Network/CURL000/LibHS.hsc" #-}
    <*> ((\hsc_ptr -> peekByteOff hsc_ptr 16) ptr >>= peekCUInt)
{-# LINE 144 "Network/CURL000/LibHS.hsc" #-}
    <*> ((\hsc_ptr -> peekByteOff hsc_ptr 24) ptr >>= peekCAString)
{-# LINE 145 "Network/CURL000/LibHS.hsc" #-}
    <*> ((\hsc_ptr -> peekByteOff hsc_ptr 32) ptr >>= peekCFeatures)
{-# LINE 146 "Network/CURL000/LibHS.hsc" #-}
    <*> ((\hsc_ptr -> peekByteOff hsc_ptr 40) ptr >>= peekCString0)
{-# LINE 147 "Network/CURL000/LibHS.hsc" #-}
    <*> ((\hsc_ptr -> peekByteOff hsc_ptr 48) ptr >>= peekCLong)
{-# LINE 148 "Network/CURL000/LibHS.hsc" #-}
    <*> ((\hsc_ptr -> peekByteOff hsc_ptr 56) ptr >>= peekCString0)
{-# LINE 149 "Network/CURL000/LibHS.hsc" #-}
    <*> ((\hsc_ptr -> peekByteOff hsc_ptr 64) ptr >>= peekCStringL)
{-# LINE 150 "Network/CURL000/LibHS.hsc" #-}
    <*> ((\hsc_ptr -> peekByteOff hsc_ptr 72) ptr >>= peekCString0)
{-# LINE 151 "Network/CURL000/LibHS.hsc" #-}
    <*> ((\hsc_ptr -> peekByteOff hsc_ptr 80) ptr >>= peekCInt)
{-# LINE 152 "Network/CURL000/LibHS.hsc" #-}
    <*> ((\hsc_ptr -> peekByteOff hsc_ptr 88) ptr >>= peekCString0)
{-# LINE 153 "Network/CURL000/LibHS.hsc" #-}
    <*> ((\hsc_ptr -> peekByteOff hsc_ptr 96) ptr >>= peekCInt)
{-# LINE 154 "Network/CURL000/LibHS.hsc" #-}
    <*> ((\hsc_ptr -> peekByteOff hsc_ptr 104) ptr >>= peekCString0)
{-# LINE 155 "Network/CURL000/LibHS.hsc" #-}

peekCString0 :: Ptr CChar -> IO String
peekCString0 ptr = if (ptr==nullPtr) then return [] else peekCAString ptr

peekCStringL :: Ptr (Ptr CChar) -> IO [String]
peekCStringL ptr = peekArray0 nullPtr ptr >>= mapM peekCAString

peekCFeatures :: CInt -> IO [CURLfeature]
peekCFeatures = return . fromCIntMask

peekCUInt :: CUInt -> IO Int
peekCUInt = return . fromIntegral

peekCInt :: CInt -> IO Int
peekCInt = return . fromIntegral

peekCLong :: CLong -> IO Int
peekCLong = return . fromIntegral



-------------------------------------------------------------------------------
-- | Start a libcurl easy session
--   (<http://curl.haxx.se/libcurl/c/curl_easy_init.html>).
-------------------------------------------------------------------------------
curl_easy_init :: IO CURL
curl_easy_init = do
  ccurl <- C.curl_easy_init; curlmvar <- newMVar ccurl
  uid <- newUnique; cbref <- newIORef []; slref <- newIORef []
  let curl = CURL uid curlmvar cbref slref
  if (ccurl/=nullPtr) then return curl else do
    desc <- C.curl_easy_strerror 2 >>= peekCString0
{-# LINE 187 "Network/CURL000/LibHS.hsc" #-}
    throwCURLE curl "curl_easy_init" desc CURLE_FAILED_INIT


-------------------------------------------------------------------------------
throwCURLE :: CURL -> String -> String -> CURLC -> IO a
throwCURLE curl func desc code = throwIO (CURLE curl func desc code)

checkCURLE :: CURL -> String -> (IO CInt) -> IO ()
checkCURLE curl func action =
  action >>= \code -> when (code/=0) $ do
    desc <- C.curl_easy_strerror code >>= peekCString0
    throwCURLE curl func desc (toCURLC code)

withCCURL :: CURL -> (Ptr C.CURL -> IO a) -> IO a
withCCURL (CURL _ curlmvar _ _) = withMVar curlmvar


-------------------------------------------------------------------------------
-- | Reset all options of a libcurl session handle
--   (<http://curl.haxx.se/libcurl/c/curl_easy_reset.html>).
-------------------------------------------------------------------------------
curl_easy_reset :: CURL -> IO ()
curl_easy_reset (CURL _ curlmvar cbref slref) =
  modifyMVar_ curlmvar $ \ccurl -> do
    when (ccurl/=nullPtr) (C.curl_easy_reset ccurl)
    freeCURL cbref slref >> return ccurl


-------------------------------------------------------------------------------
-- | End a libcurl easy session
--   (<http://curl.haxx.se/libcurl/c/curl_easy_cleanup.html>).
-------------------------------------------------------------------------------
curl_easy_cleanup :: CURL -> IO ()
curl_easy_cleanup (CURL _ curlmvar cbref slref) =
  modifyMVar_ curlmvar $ \ccurl -> do
    when (ccurl/=nullPtr) (C.curl_easy_cleanup ccurl)
    freeCURL cbref slref >> return nullPtr

freeCURL :: IORef [CURLCB] -> IORef [CURLSL] -> IO ()
freeCURL cbref slref = do
  atomicModifyIORef cbref (\cbs -> ([],cbs)) >>= mapM_ freeCB
  atomicModifyIORef slref (\sls -> ([],sls)) >>= mapM_ freeSL


-------------------------------------------------------------------------------
-- | Perform a file transfer
--   (<http://curl.haxx.se/libcurl/c/curl_easy_perform.html>).
-------------------------------------------------------------------------------
curl_easy_perform :: CURL -> IO ()
curl_easy_perform curl =
  withCCURL curl (checkCURLE curl "curl_easy_perform" . C.curl_easy_perform)


-------------------------------------------------------------------------------
-- | Receives raw data on an @easy@ connection
--   (<http://curl.haxx.se/libcurl/c/curl_easy_recv.html>).
-------------------------------------------------------------------------------
curl_easy_recv :: CURL -> Int -> IO ByteString
curl_easy_recv curl len =
  withCCURL curl $ \ccurl -> alloca $ \nptr -> allocaBytes len $ \buff -> do
    let check = checkCURLE curl "curl_easy_recv"
    check $ C.curl_easy_recv ccurl buff (fromIntegral len) nptr
    n <- fmap fromIntegral (peek nptr)
    packCStringLen (castPtr buff, n)


-------------------------------------------------------------------------------
-- | Sends raw data over an @easy@ connection
--   (<http://curl.haxx.se/libcurl/c/curl_easy_send.html>).
-------------------------------------------------------------------------------
curl_easy_send :: CURL -> ByteString -> IO Int
curl_easy_send curl bs =
  withCCURL curl $ \ccurl -> alloca $ \nptr -> do
    let check = checkCURLE curl "curl_easy_send"
    check $ unsafeUseAsCStringLen bs $ \(cs, cl) ->
      C.curl_easy_send ccurl (castPtr cs) (fromIntegral cl) nptr
    fmap fromIntegral (peek nptr)


-------------------------------------------------------------------------------
-- | Extract information from a curl handle
--   (<http://curl.haxx.se/libcurl/c/curl_easy_getinfo.html>).
-------------------------------------------------------------------------------

{-# LINE 271 "Network/CURL000/LibHS.hsc" #-}
curl_easy_getinfo :: CURL -> CURLinfo a -> IO a
curl_easy_getinfo curl opt = withCCURL curl $ \ccurl ->
  let getopt :: Storable x => CInt -> (Ptr x -> IO a) -> IO a
      getopt x fpeek = alloca $ \ptr -> getptr x (castPtr ptr) >> fpeek ptr
      getptr x ptr = check $ C.curl_easy_getinfo ccurl x ptr
      check = checkCURLE curl "curl_easy_getinfo"
  in case opt of
    CURLINFO_EFFECTIVE_URL -> getopt 1048577 getString
{-# LINE 279 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_RESPONSE_CODE -> getopt 2097154 getCLong
{-# LINE 280 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_HTTP_CONNECTCODE -> getopt 2097174 getCLong
{-# LINE 281 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_FILETIME -> getopt 2097166 getTime
{-# LINE 282 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_TOTAL_TIME -> getopt 3145731 getDouble
{-# LINE 283 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_NAMELOOKUP_TIME -> getopt 3145732 getDouble
{-# LINE 284 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_CONNECT_TIME -> getopt 3145733 getDouble
{-# LINE 285 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_APPCONNECT_TIME -> getopt 3145761 getDouble
{-# LINE 286 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_PRETRANSFER_TIME -> getopt 3145734 getDouble
{-# LINE 287 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_STARTTRANSFER_TIME -> getopt 3145745 getDouble
{-# LINE 288 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_REDIRECT_TIME -> getopt 3145747 getDouble
{-# LINE 289 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_REDIRECT_COUNT -> getopt 2097172 getCLong
{-# LINE 290 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_REDIRECT_URL -> getopt 1048607 getString
{-# LINE 291 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_SIZE_UPLOAD -> getopt 3145735 getDouble
{-# LINE 292 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_SIZE_DOWNLOAD -> getopt 3145736 getDouble
{-# LINE 293 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_SPEED_DOWNLOAD -> getopt 3145737 getDouble
{-# LINE 294 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_SPEED_UPLOAD -> getopt 3145738 getDouble
{-# LINE 295 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_HEADER_SIZE -> getopt 2097163 getCLong
{-# LINE 296 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_REQUEST_SIZE -> getopt 2097164 getCLong
{-# LINE 297 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_SSL_VERIFYRESULT -> getopt 2097165 getCLong
{-# LINE 298 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_SSL_ENGINES -> getopt 4194331 getSList
{-# LINE 299 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_CONTENT_LENGTH_DOWNLOAD -> getopt 3145743 getDouble
{-# LINE 300 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_CONTENT_LENGTH_UPLOAD -> getopt 3145744 getDouble
{-# LINE 301 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_CONTENT_TYPE -> getopt 1048594 getString
{-# LINE 302 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_HTTPAUTH_AVAIL -> getopt 2097175 getAuth
{-# LINE 303 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_PROXYAUTH_AVAIL -> getopt 2097176 getAuth
{-# LINE 304 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_OS_ERRNO -> getopt 2097177 getCLong
{-# LINE 305 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_NUM_CONNECTS -> getopt 2097178 getCLong
{-# LINE 306 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_PRIMARY_IP -> getopt 1048608 getString
{-# LINE 307 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_PRIMARY_PORT -> getopt 2097192 getCLong
{-# LINE 308 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_LOCAL_IP -> getopt 1048617 getString
{-# LINE 309 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_LOCAL_PORT -> getopt 2097194 getCLong
{-# LINE 310 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_COOKIELIST -> getopt 4194332 getSList
{-# LINE 311 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_LASTSOCKET -> getopt 2097181 getCLong
{-# LINE 312 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_FTP_ENTRY_PATH -> getopt 1048606 getString
{-# LINE 313 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_CERTINFO -> getopt 4194338 getCerts
{-# LINE 314 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_CONDITION_UNMET -> getopt 2097187 getBool
{-# LINE 315 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_RTSP_SESSION_ID -> getopt 1048612 getString
{-# LINE 316 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_RTSP_CLIENT_CSEQ -> getopt 2097189 getCLong
{-# LINE 317 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_RTSP_SERVER_CSEQ -> getopt 2097190 getCLong
{-# LINE 318 "Network/CURL000/LibHS.hsc" #-}
    CURLINFO_RTSP_CSEQ_RECV -> getopt 2097191 getCLong
{-# LINE 319 "Network/CURL000/LibHS.hsc" #-}

getString :: Ptr (Ptr CChar) -> IO String
getString ptr = peek ptr >>= peekCString0

getDouble :: Ptr CDouble -> IO Double
getDouble = fmap realToFrac . peek

getCLong :: Ptr CLong -> IO CLong
getCLong = peek

getBool :: Ptr CLong -> IO Bool
getBool = fmap toBool . peek

getAuth :: Ptr CLong -> IO [CURLauth]
getAuth = fmap fromCLongMask . peek

getTime :: Ptr CLong -> IO (Maybe UTCTime)
getTime =
  let mconv f x = if (x==(-1) || x==0) then Nothing else Just (f x)
  in  fmap (mconv (posixSecondsToUTCTime . realToFrac)) . peek

getCerts :: Ptr (Ptr C.CURLcerts) -> IO [[String]]
getCerts ptr =
  peek ptr >>= \certs -> if (certs==nullPtr) then return [] else
    peek certs >>= \(C.CURLcerts len tab) ->
      peekArray (fromIntegral len) tab >>= mapM peekCURLslist

getSList :: Ptr (Ptr C.CURLslist) -> IO [String]
getSList ptr =
  peek ptr >>= \slist -> do
    strings <- peekCURLslist slist
    C.curl_slist_free_all slist
    return strings

peekCURLslist :: Ptr C.CURLslist -> IO [String]
peekCURLslist ptr =
  if (ptr==nullPtr) then return [] else
    peek ptr >>= \(C.CURLslist cs csl) -> do
      slist_head <- peekCAString cs
      slist_tail <- peekCURLslist csl
      return (slist_head : slist_tail)


-------------------------------------------------------------------------------
-- | 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@(CURL _ _ cbref slref) opts =
  withCCURL curl $ \ccurl -> forM_ opts $ \opt ->
    checkCURLE curl "curl_easy_setopt" $ case opt of

  
{-# LINE 372 "Network/CURL000/LibHS.hsc" #-}

  ---- CALLBACK OPTIONS -------------------------------------------------------
  CURLOPT_WRITEFUNCTION x -> curlcb FWRITE ccurl 20011 x
{-# LINE 375 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_READFUNCTION x -> curlcb FREAD ccurl 20012 x
{-# LINE 376 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_HEADERFUNCTION x -> curlcb FHEADER ccurl 20079 x
{-# LINE 377 "Network/CURL000/LibHS.hsc" #-}

  ---- BEHAVIOR OPTIONS -------------------------------------------------------
  CURLOPT_VERBOSE x -> bool ccurl 41 x
{-# LINE 380 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_HEADER x -> bool ccurl 42 x
{-# LINE 381 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_NOPROGRESS x -> bool ccurl 43 x
{-# LINE 382 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_NOSIGNAL x -> bool ccurl 99 x
{-# LINE 383 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_WILDCARDMATCH x -> bool ccurl 197 x
{-# LINE 384 "Network/CURL000/LibHS.hsc" #-}

  ---- ERROR OPTIONS ----------------------------------------------------------
  -- CURLOPT_ERRORBUFFER
  -- CURLOPT_STDERR
  CURLOPT_FAILONERROR x -> bool ccurl 45 x
{-# LINE 389 "Network/CURL000/LibHS.hsc" #-}

  ---- NETWORK OPTIONS --------------------------------------------------------
  CURLOPT_URL x -> string ccurl 10002 x
{-# LINE 392 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_PROTOCOLS x -> enum ccurl 181 x
{-# LINE 393 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_REDIR_PROTOCOLS x -> enum ccurl 182 x
{-# LINE 394 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_PROXY x -> string ccurl 10004 x
{-# LINE 395 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_PROXYPORT x -> clong ccurl 59 x
{-# LINE 396 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_PROXYTYPE x -> enum ccurl 101 x
{-# LINE 397 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_NOPROXY x -> string ccurl 10177 x
{-# LINE 398 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_HTTPPROXYTUNNEL x -> bool ccurl 61 x
{-# LINE 399 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SOCKS5_GSSAPI_SERVICE x -> string ccurl 10179 x
{-# LINE 400 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SOCKS5_GSSAPI_NEC x -> bool ccurl 180 x
{-# LINE 401 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_INTERFACE x -> string ccurl 10062 x
{-# LINE 402 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_LOCALPORT x -> clong ccurl 139 x
{-# LINE 403 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_LOCALPORTRANGE x -> clong ccurl 140 x
{-# LINE 404 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_DNS_CACHE_TIMEOUT x -> clong ccurl 92 x
{-# LINE 405 "Network/CURL000/LibHS.hsc" #-}
  -- #{setopt CURLOPT_DNS_USE_GLOBAL_CACHE   , bool     }
  CURLOPT_BUFFERSIZE x -> clong ccurl 98 x
{-# LINE 407 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_PORT x -> clong ccurl 3 x
{-# LINE 408 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_TCP_NODELAY x -> bool ccurl 121 x
{-# LINE 409 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_ADDRESS_SCOPE x -> clong ccurl 171 x
{-# LINE 410 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_TCP_KEEPALIVE x -> bool ccurl 213 x
{-# LINE 411 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_TCP_KEEPIDLE x -> clong ccurl 214 x
{-# LINE 412 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_TCP_KEEPINTVL x -> clong ccurl 215 x
{-# LINE 413 "Network/CURL000/LibHS.hsc" #-}

  ---- NAMES and PASSWORDS OPTIONS (Authentication) ---------------------------
  CURLOPT_NETRC x -> enum ccurl 51 x
{-# LINE 416 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_NETRC_FILE x -> string ccurl 10118 x
{-# LINE 417 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_USERPWD x -> string ccurl 10005 x
{-# LINE 418 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_PROXYUSERPWD x -> string ccurl 10006 x
{-# LINE 419 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_USERNAME x -> string ccurl 10173 x
{-# LINE 420 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_PASSWORD x -> string ccurl 10174 x
{-# LINE 421 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_PROXYUSERNAME x -> string ccurl 10175 x
{-# LINE 422 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_PROXYPASSWORD x -> string ccurl 10176 x
{-# LINE 423 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_HTTPAUTH x -> enum ccurl 107 x
{-# LINE 424 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_TLSAUTH_TYPE x -> string ccurl 10206 x
{-# LINE 425 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_TLSAUTH_USERNAME x -> string ccurl 10204 x
{-# LINE 426 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_TLSAUTH_PASSWORD x -> string ccurl 10205 x
{-# LINE 427 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_PROXYAUTH x -> enum ccurl 111 x
{-# LINE 428 "Network/CURL000/LibHS.hsc" #-}

  ---- HTTP OPTIONS -----------------------------------------------------------
  CURLOPT_AUTOREFERER x -> bool ccurl 58 x
{-# LINE 431 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_ACCEPT_ENCODING x -> string ccurl 10102 x
{-# LINE 432 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_TRANSFER_ENCODING x -> bool ccurl 207 x
{-# LINE 433 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_FOLLOWLOCATION x -> bool ccurl 52 x
{-# LINE 434 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_UNRESTRICTED_AUTH x -> bool ccurl 105 x
{-# LINE 435 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_MAXREDIRS x -> clong ccurl 68 x
{-# LINE 436 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_POSTREDIR x -> enum ccurl 161 x
{-# LINE 437 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_PUT x -> bool ccurl 54 x
{-# LINE 438 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_POST x -> bool ccurl 47 x
{-# LINE 439 "Network/CURL000/LibHS.hsc" #-}
  -- #{setopt CURLOPT_POSTFIELDS             , buffer   }
  CURLOPT_POSTFIELDSIZE x -> clong ccurl 60 x
{-# LINE 441 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_POSTFIELDSIZE_LARGE x -> int64 ccurl 30120 x
{-# LINE 442 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_COPYPOSTFIELDS x -> string ccurl 10165 x
{-# LINE 443 "Network/CURL000/LibHS.hsc" #-}
  -- CURLOPT_HTTPPOST
  CURLOPT_REFERER x -> string ccurl 10016 x
{-# LINE 445 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_USERAGENT x -> string ccurl 10018 x
{-# LINE 446 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_HTTPHEADER x -> slist ccurl 10023 x
{-# LINE 447 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_HTTP200ALIASES x -> slist ccurl 10104 x
{-# LINE 448 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_COOKIE x -> string ccurl 10022 x
{-# LINE 449 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_COOKIEFILE x -> string ccurl 10031 x
{-# LINE 450 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_COOKIEJAR x -> string ccurl 10082 x
{-# LINE 451 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_COOKIESESSION x -> bool ccurl 96 x
{-# LINE 452 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_COOKIELIST x -> string ccurl 10135 x
{-# LINE 453 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_HTTPGET x -> bool ccurl 80 x
{-# LINE 454 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_HTTP_VERSION x -> enum ccurl 84 x
{-# LINE 455 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_IGNORE_CONTENT_LENGTH x -> bool ccurl 136 x
{-# LINE 456 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_HTTP_CONTENT_DECODING x -> bool ccurl 158 x
{-# LINE 457 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_HTTP_TRANSFER_DECODING x -> bool ccurl 157 x
{-# LINE 458 "Network/CURL000/LibHS.hsc" #-}

  ---- SMTP OPTIONS -----------------------------------------------------------
  CURLOPT_MAIL_FROM x -> string ccurl 10186 x
{-# LINE 461 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_MAIL_RCPT x -> slist ccurl 10187 x
{-# LINE 462 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_MAIL_AUTH x -> string ccurl 10217 x
{-# LINE 463 "Network/CURL000/LibHS.hsc" #-}

  ---- TFTP OPTIONS -----------------------------------------------------------
  CURLOPT_TFTP_BLKSIZE x -> clong ccurl 178 x
{-# LINE 466 "Network/CURL000/LibHS.hsc" #-}

  ---- FTP OPTIONS ------------------------------------------------------------
  CURLOPT_FTPPORT x -> string ccurl 10017 x
{-# LINE 469 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_QUOTE x -> slist ccurl 10028 x
{-# LINE 470 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_POSTQUOTE x -> slist ccurl 10039 x
{-# LINE 471 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_PREQUOTE x -> slist ccurl 10093 x
{-# LINE 472 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_DIRLISTONLY x -> bool ccurl 48 x
{-# LINE 473 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_APPEND x -> bool ccurl 50 x
{-# LINE 474 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_FTP_USE_EPRT x -> bool ccurl 106 x
{-# LINE 475 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_FTP_USE_EPSV x -> bool ccurl 85 x
{-# LINE 476 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_FTP_USE_PRET x -> bool ccurl 188 x
{-# LINE 477 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_FTP_CREATE_MISSING_DIRS x -> enum ccurl 110 x
{-# LINE 478 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_FTP_RESPONSE_TIMEOUT x -> clong ccurl 112 x
{-# LINE 479 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_FTP_ALTERNATIVE_TO_USER x -> string ccurl 10147 x
{-# LINE 480 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_FTP_SKIP_PASV_IP x -> bool ccurl 137 x
{-# LINE 481 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_FTPSSLAUTH x -> enum ccurl 129 x
{-# LINE 482 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_FTP_SSL_CCC x -> enum ccurl 154 x
{-# LINE 483 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_FTP_ACCOUNT x -> string ccurl 10134 x
{-# LINE 484 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_FTP_FILEMETHOD x -> enum ccurl 138 x
{-# LINE 485 "Network/CURL000/LibHS.hsc" #-}

  ---- RTSP OPTIONS -----------------------------------------------------------
  
{-# LINE 488 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_RTSP_REQUEST x -> enum ccurl 189 x
{-# LINE 489 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_RTSP_SESSION_ID x -> string ccurl 10190 x
{-# LINE 490 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_RTSP_STREAM_URI x -> string ccurl 10191 x
{-# LINE 491 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_RTSP_TRANSPORT x -> string ccurl 10192 x
{-# LINE 492 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_RTSP_HEADER x -> slist ccurl 10023 x
{-# LINE 493 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_RTSP_CLIENT_CSEQ x -> clong ccurl 193 x
{-# LINE 494 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_RTSP_SERVER_CSEQ x -> clong ccurl 194 x
{-# LINE 495 "Network/CURL000/LibHS.hsc" #-}

  ---- PROTOCOL OPTIONS -------------------------------------------------------
  CURLOPT_TRANSFERTEXT x -> bool ccurl 53 x
{-# LINE 498 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_PROXY_TRANSFER_MODE x -> bool ccurl 166 x
{-# LINE 499 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_CRLF x -> bool ccurl 27 x
{-# LINE 500 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_RANGE x -> string ccurl 10007 x
{-# LINE 501 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_RESUME_FROM x -> clong ccurl 21 x
{-# LINE 502 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_RESUME_FROM_LARGE x -> int64 ccurl 30116 x
{-# LINE 503 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_CUSTOMREQUEST x -> string ccurl 10036 x
{-# LINE 504 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_FILETIME x -> bool ccurl 69 x
{-# LINE 505 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_NOBODY x -> bool ccurl 44 x
{-# LINE 506 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_INFILESIZE x -> clong ccurl 14 x
{-# LINE 507 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_INFILESIZE_LARGE x -> int64 ccurl 30115 x
{-# LINE 508 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_UPLOAD x -> bool ccurl 46 x
{-# LINE 509 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_MAXFILESIZE x -> clong ccurl 114 x
{-# LINE 510 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_MAXFILESIZE_LARGE x -> int64 ccurl 30117 x
{-# LINE 511 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_TIMECONDITION x -> enum ccurl 33 x
{-# LINE 512 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_TIMEVALUE x -> time ccurl 34 x
{-# LINE 513 "Network/CURL000/LibHS.hsc" #-}

  ---- CONNECTION OPTIONS -----------------------------------------------------
  CURLOPT_TIMEOUT x -> clong ccurl 13 x
{-# LINE 516 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_TIMEOUT_MS x -> clong ccurl 155 x
{-# LINE 517 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_LOW_SPEED_LIMIT x -> clong ccurl 19 x
{-# LINE 518 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_LOW_SPEED_TIME x -> clong ccurl 20 x
{-# LINE 519 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_MAX_SEND_SPEED_LARGE x -> int64 ccurl 30145 x
{-# LINE 520 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_MAX_RECV_SPEED_LARGE x -> int64 ccurl 30146 x
{-# LINE 521 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_MAXCONNECTS x -> clong ccurl 71 x
{-# LINE 522 "Network/CURL000/LibHS.hsc" #-}
  -- #{setopt CURLOPT_CLOSEPOLICY            , enum     }
  CURLOPT_FRESH_CONNECT x -> bool ccurl 74 x
{-# LINE 524 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_FORBID_REUSE x -> bool ccurl 75 x
{-# LINE 525 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_CONNECTTIMEOUT x -> clong ccurl 78 x
{-# LINE 526 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_CONNECTTIMEOUT_MS x -> clong ccurl 156 x
{-# LINE 527 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_IPRESOLVE x -> enum ccurl 113 x
{-# LINE 528 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_CONNECT_ONLY x -> bool ccurl 141 x
{-# LINE 529 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_USE_SSL x -> enum ccurl 119 x
{-# LINE 530 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_RESOLVE x -> slist ccurl 10203 x
{-# LINE 531 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_DNS_SERVERS x -> string ccurl 10211 x
{-# LINE 532 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_ACCEPTTIMEOUT_MS x -> clong ccurl 212 x
{-# LINE 533 "Network/CURL000/LibHS.hsc" #-}

  ---- SSL and SECURITY OPTIONS -----------------------------------------------
  CURLOPT_SSLCERT x -> string ccurl 10025 x
{-# LINE 536 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SSLCERTTYPE x -> string ccurl 10086 x
{-# LINE 537 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SSLKEY x -> string ccurl 10087 x
{-# LINE 538 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SSLKEYTYPE x -> string ccurl 10088 x
{-# LINE 539 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_KEYPASSWD x -> string ccurl 10026 x
{-# LINE 540 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SSLENGINE x -> string ccurl 10089 x
{-# LINE 541 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SSLENGINE_DEFAULT x -> bool ccurl 90 x
{-# LINE 542 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SSLVERSION x -> enum ccurl 32 x
{-# LINE 543 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SSL_VERIFYPEER x -> bool ccurl 64 x
{-# LINE 544 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_CAINFO x -> string ccurl 10065 x
{-# LINE 545 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_ISSUERCERT x -> string ccurl 10170 x
{-# LINE 546 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_CAPATH x -> string ccurl 10097 x
{-# LINE 547 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_CRLFILE x -> string ccurl 10169 x
{-# LINE 548 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SSL_VERIFYHOST x -> bool2 ccurl 81 x
{-# LINE 549 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_CERTINFO x -> bool ccurl 172 x
{-# LINE 550 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_RANDOM_FILE x -> string ccurl 10076 x
{-# LINE 551 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_EGDSOCKET x -> string ccurl 10077 x
{-# LINE 552 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SSL_CIPHER_LIST x -> string ccurl 10083 x
{-# LINE 553 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SSL_SESSIONID_CACHE x -> bool ccurl 150 x
{-# LINE 554 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SSL_OPTIONS x -> enum ccurl 216 x
{-# LINE 555 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_KRBLEVEL x -> string ccurl 10063 x
{-# LINE 556 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_GSSAPI_DELEGATION x -> enum ccurl 210 x
{-# LINE 557 "Network/CURL000/LibHS.hsc" #-}

  ---- SSH OPTIONS ------------------------------------------------------------
  CURLOPT_SSH_AUTH_TYPES x -> enum ccurl 151 x
{-# LINE 560 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SSH_HOST_PUBLIC_KEY_MD5 x -> string ccurl 10162 x
{-# LINE 561 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SSH_PUBLIC_KEYFILE x -> string ccurl 10152 x
{-# LINE 562 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SSH_PRIVATE_KEYFILE x -> string ccurl 10153 x
{-# LINE 563 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_SSH_KNOWNHOSTS x -> string ccurl 10183 x
{-# LINE 564 "Network/CURL000/LibHS.hsc" #-}
  -- CURLOPT_SSH_KEYFUNCTION
  -- CURLOPT_SSH_KEYDATA

  ---- OTHER OPTIONS ----------------------------------------------------------
  -- CURLOPT_PRIVATE
  CURLOPT_SHARE x -> curlsh ccurl 10100 x
{-# LINE 570 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_NEW_FILE_PERMS x -> clong ccurl 159 x
{-# LINE 571 "Network/CURL000/LibHS.hsc" #-}
  CURLOPT_NEW_DIRECTORY_PERMS x -> clong ccurl 160 x
{-# LINE 572 "Network/CURL000/LibHS.hsc" #-}

  ---- TELNET OPTIONS ---------------------------------------------------------
  CURLOPT_TELNETOPTIONS x -> slist ccurl 10070 x
{-# LINE 575 "Network/CURL000/LibHS.hsc" #-}

  where
    ---------------------------------------------------------------------------
    enum  ccurl copt x = C.curl_easy_setopt'Long ccurl copt (toCLong      x)
    bool  ccurl copt x = C.curl_easy_setopt'Long ccurl copt (fromBool     x)
    bool2 ccurl copt x = C.curl_easy_setopt'Long ccurl copt (fromBool2    x)
    time  ccurl copt x = C.curl_easy_setopt'Long ccurl copt (fromUTCTime  x)
    clong ccurl copt x = C.curl_easy_setopt'Long ccurl copt (fromIntegral x)
    int64 ccurl copt x = C.curl_easy_setopt'COff ccurl copt (fromIntegral x)
    fromUTCTime = truncate . utcTimeToPOSIXSeconds
    fromBool2 False = 0; fromBool2 True = 2
    ---------------------------------------------------------------------------
    string ccurl copt x = withCAString x $ \p ->
      C.curl_easy_setopt'DPtr ccurl copt (castPtr p)
    ---------------------------------------------------------------------------
    slist ccurl copt x = makeSL slref ccurl copt x
    ---------------------------------------------------------------------------
    curlcb :: CURLCBT a -> Ptr C.CURL -> CInt -> Maybe a -> IO CInt
    curlcb cbt ccurl copt x = makeCB cbref cbt ccurl copt x
    ---------------------------------------------------------------------------
    curlsh ccurl copt Nothing = C.curl_easy_setopt'DPtr ccurl copt nullPtr
    curlsh ccurl copt (Just (CURLSH _ mvar)) =
      withMVar mvar $ \(ccurlsh,_,_) ->
        C.curl_easy_setopt'DPtr ccurl copt (castPtr ccurlsh)


-------------------------------------------------------------------------------
wrapSL :: [String] -> IO (Maybe (Ptr C.CURLslist))
wrapSL = foldM wrap (Just nullPtr)
  where
  wrap Nothing _ = return Nothing
  wrap (Just sl) xs =
    withCAString xs (C.curl_slist_append sl) >>= \nsl ->
      if (nsl/=nullPtr) then return (Just nsl) else do
         when (sl/=nullPtr) (C.curl_slist_free_all sl)
         return Nothing

freeSL :: CURLSL -> IO ()
freeSL (_,sl) = when (sl/=nullPtr) (C.curl_slist_free_all sl)

makeSL :: IORef [CURLSL] -> Ptr C.CURL -> CInt -> [String] -> IO CInt
makeSL slref ccurl copt xs =
  let cons sl (tokeep, tofree) = ((copt,sl):tokeep, tofree)
      keep 0 sl sls = cons sl $ partition ((/=copt) . fst) sls
      keep _ sl sls = cons sl $ (sls,[])
  in  wrapSL xs >>= \msl -> case msl of
        Nothing -> return 27
{-# LINE 622 "Network/CURL000/LibHS.hsc" #-}
        Just sl -> do
          code <- C.curl_easy_setopt'DPtr ccurl copt (castPtr sl)
          atomicModifyIORef slref (keep code sl) >>= mapM_ freeSL
          return code


-------------------------------------------------------------------------------
wrapCB :: CURLCBT a -> a -> IO (FunPtr ())
wrapCB cbt = case cbt of
  FWRITE  -> fmap castFunPtr . C.wrapCURL_write_callback  . write_callback
  FREAD   -> fmap castFunPtr . C.wrapCURL_read_callback   . read_callback
  FHEADER -> fmap castFunPtr . C.wrapCURL_header_callback . header_callback

freeCB :: CURLCB -> IO ()
freeCB (CURLCB _ fp) = when (fp/=nullFunPtr) (freeHaskellFunPtr fp)

makeCB
  :: IORef [CURLCB] -> CURLCBT a -> Ptr C.CURL -> CInt -> Maybe a -> IO CInt
makeCB cbref cbt ccurl copt mcb =
  let comp :: CURLCBT a -> CURLCB -> Bool
      comp FWRITE  (CURLCB FWRITE  _) = False; comp FWRITE  _ = True
      comp FREAD   (CURLCB FREAD   _) = False; comp FREAD   _ = True
      comp FHEADER (CURLCB FHEADER _) = False; comp FHEADER _ = True
      cons fp (tokeep, tofree) = ((CURLCB cbt fp):tokeep, tofree)
      keep 0 fp cbs = cons fp $ partition (comp cbt) cbs
      keep _ fp cbs = cons fp $ (cbs,[])
  in  maybe (return nullFunPtr) (wrapCB cbt) mcb >>= \fp -> do
        code <- C.curl_easy_setopt'FPtr ccurl copt fp
        atomicModifyIORef cbref (keep code fp) >>= mapM_ freeCB
        return code


-------------------------------------------------------------------------------
write_callback :: CURL_write_callback -> C.CURL_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 -> 268435457
{-# LINE 662 "Network/CURL000/LibHS.hsc" #-}


-------------------------------------------------------------------------------
read_callback :: CURL_read_callback -> C.CURL_read_callback
read_callback fread buff size nmemb _ = do
  let buffLen = fromIntegral (size * nmemb)
  stat <- fread buffLen
  case stat of
    CURL_READFUNC_PAUSE -> return 268435457
{-# LINE 671 "Network/CURL000/LibHS.hsc" #-}
    CURL_READFUNC_ABORT -> return 268435456
{-# LINE 672 "Network/CURL000/LibHS.hsc" #-}
    CURL_READFUNC_OK bs -> unsafeUseAsCStringLen (BS.take buffLen bs)
      (\(cs, cl) -> copyBytes buff cs cl >> return (fromIntegral cl))


-------------------------------------------------------------------------------
header_callback :: CURL_header_callback -> C.CURL_header_callback
header_callback fheader ptr size nmemb _ = do
  stat <- packCStringLen (ptr, fromIntegral (size * nmemb)) >>= fheader
  return $ case stat of
    CURL_HEADERFUNC_OK   -> (size * nmemb)
    CURL_HEADERFUNC_FAIL -> 0


-------------------------------------------------------------------------------
-- | Create a shared object
--   (<http://curl.haxx.se/libcurl/c/curl_share_init.html>).
-------------------------------------------------------------------------------
curl_share_init :: IO CURLSH
curl_share_init = bracketOnError createcurlsh curl_share_cleanup setupcurlsh
  where
  -----------------
  createcurlsh = do
    ccurlsh <- C.curl_share_init
    (f1,f2) <- if (ccurlsh == nullPtr)
      then return (nullFunPtr, nullFunPtr)
      else do
        shlocks <- newSHLocks
        f1 <- C.wrapCURL_lock_function   (lock_function   shlocks)
        f2 <- C.wrapCURL_unlock_function (unlock_function shlocks)
        return (castFunPtr f1, castFunPtr f2)
    uid <- newUnique; mvar <- newMVar (ccurlsh,f1,f2)
    return (CURLSH uid mvar)
  ------------------------------------
  setupcurlsh curlsh@(CURLSH _ mvar) =
    withMVar mvar $ \(ccurlsh,f1,f2) -> do
      let func = "curl_share_init"
      if (ccurlsh == nullPtr)
        then do
          let getstrerror x = C.curl_easy_strerror x >>= peekCString0
          desc <- getstrerror 2
{-# LINE 712 "Network/CURL000/LibHS.hsc" #-}
          throwCURLSHE curlsh func desc CURLSHE_FAILED_INIT
        else do
          let withCHECK = checkCURLSHE curlsh func
          let setshopt = C.curl_share_setopt'FPtr ccurlsh
          withCHECK $ setshopt 3 f1
{-# LINE 717 "Network/CURL000/LibHS.hsc" #-}
          withCHECK $ setshopt 4 f2
{-# LINE 718 "Network/CURL000/LibHS.hsc" #-}
          return curlsh


-------------------------------------------------------------------------------
-- | Clean up a shared object
--   (<http://curl.haxx.se/libcurl/c/curl_share_cleanup.html>).
-------------------------------------------------------------------------------
curl_share_cleanup :: CURLSH -> IO ()
curl_share_cleanup curlsh@(CURLSH _ mvar) =
  let withCHECK = checkCURLSHE curlsh "curl_share_cleanup"
  in  modifyMVar_ mvar $ \(ccurlsh,f1,f2) -> do
        when (ccurlsh/=nullPtr) (withCHECK $ C.curl_share_cleanup ccurlsh)
        when (f1/=nullFunPtr) (freeHaskellFunPtr f1)
        when (f2/=nullFunPtr) (freeHaskellFunPtr f2)
        return (nullPtr,nullFunPtr,nullFunPtr)


-------------------------------------------------------------------------------
-- | Set options for a shared object
--   (<http://curl.haxx.se/libcurl/c/curl_share_setopt.html>).
-------------------------------------------------------------------------------

{-# LINE 740 "Network/CURL000/LibHS.hsc" #-}
curl_share_setopt :: CURLSH -> [CURLSHoption] -> IO ()
curl_share_setopt curlsh@(CURLSH _ mvar) opts =
  withMVar mvar $ \(ccurlsh,_,_) -> do
    let func = "curl_share_setopt"
    when (ccurlsh==nullPtr) $ do
      desc <- C.curl_share_strerror 3 >>= peekCString0
{-# LINE 746 "Network/CURL000/LibHS.hsc" #-}
      throwCURLSHE curlsh func desc CURLSHE_INVALID
    let enum copt x = C.curl_share_setopt'Long ccurlsh copt (toCLong x)
    flip mapM_ opts $ \opt -> checkCURLSHE curlsh func $ case opt of
      CURLSHOPT_SHARE x -> enum 1 x
{-# LINE 750 "Network/CURL000/LibHS.hsc" #-}
      CURLSHOPT_UNSHARE x -> enum 2 x
{-# LINE 751 "Network/CURL000/LibHS.hsc" #-}


-------------------------------------------------------------------------------
throwCURLSHE :: CURLSH -> String -> String -> CURLSHC -> IO a
throwCURLSHE curlsh func desc code = throwIO (CURLSHE curlsh func desc code)

checkCURLSHE :: CURLSH -> String -> (IO CInt) -> IO ()
checkCURLSHE curlsh func action =
  action >>= \code -> when (code/=0) $ do
    desc <- C.curl_share_strerror code >>= peekCString0
    throwCURLSHE curlsh func desc (toCURLSHC code)


-------------------------------------------------------------------------------
type SHLocks  = MVar [(SHLockID, SHLock)]
type SHLock   = MVar ()
type SHLockID = CInt

newSHLocks :: IO SHLocks
newSHLocks = newMVar []

getSHLock :: SHLock -> IO ()
getSHLock shlock = takeMVar shlock

putSHLock :: SHLock -> IO ()
putSHLock shlock = tryPutMVar shlock () >> return ()

lookupSHLock :: SHLocks -> SHLockID -> IO SHLock
lookupSHLock mvar shlockid =
  modifyMVar mvar $ \shlocks ->
    case (lookup shlockid shlocks) of
      Just shlock -> return (shlocks, shlock)
      Nothing     -> newMVar () >>= \nl -> return ((shlockid, nl):shlocks, nl)

lock_function :: SHLocks -> C.CURL_lock_function
lock_function shlocks _ccurl lockdata _lockaccess _usrptr =
  lookupSHLock shlocks lockdata >>= getSHLock

unlock_function :: SHLocks -> C.CURL_unlock_function
unlock_function shlocks _ccurl lockdata _usrptr =
  lookupSHLock shlocks lockdata >>= putSHLock