{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)

The HTTP message headers associated with a request or response.
-}

module GI.Soup.Structs.MessageHeaders
    ( 

-- * Exported types
    MessageHeaders(..)                      ,
    noMessageHeaders                        ,


 -- * Methods
-- ** messageHeadersAppend
    messageHeadersAppend                    ,


-- ** messageHeadersCleanConnectionHeaders
    messageHeadersCleanConnectionHeaders    ,


-- ** messageHeadersClear
    messageHeadersClear                     ,


-- ** messageHeadersForeach
    messageHeadersForeach                   ,


-- ** messageHeadersFree
    messageHeadersFree                      ,


-- ** messageHeadersFreeRanges
    messageHeadersFreeRanges                ,


-- ** messageHeadersGet
    messageHeadersGet                       ,


-- ** messageHeadersGetContentDisposition
    messageHeadersGetContentDisposition     ,


-- ** messageHeadersGetContentLength
    messageHeadersGetContentLength          ,


-- ** messageHeadersGetContentRange
    messageHeadersGetContentRange           ,


-- ** messageHeadersGetContentType
    messageHeadersGetContentType            ,


-- ** messageHeadersGetEncoding
    messageHeadersGetEncoding               ,


-- ** messageHeadersGetExpectations
    messageHeadersGetExpectations           ,


-- ** messageHeadersGetHeadersType
    messageHeadersGetHeadersType            ,


-- ** messageHeadersGetList
    messageHeadersGetList                   ,


-- ** messageHeadersGetOne
    messageHeadersGetOne                    ,


-- ** messageHeadersGetRanges
    messageHeadersGetRanges                 ,


-- ** messageHeadersHeaderContains
    messageHeadersHeaderContains            ,


-- ** messageHeadersHeaderEquals
    messageHeadersHeaderEquals              ,


-- ** messageHeadersNew
    messageHeadersNew                       ,


-- ** messageHeadersRemove
    messageHeadersRemove                    ,


-- ** messageHeadersReplace
    messageHeadersReplace                   ,


-- ** messageHeadersSetContentDisposition
    messageHeadersSetContentDisposition     ,


-- ** messageHeadersSetContentLength
    messageHeadersSetContentLength          ,


-- ** messageHeadersSetContentRange
    messageHeadersSetContentRange           ,


-- ** messageHeadersSetContentType
    messageHeadersSetContentType            ,


-- ** messageHeadersSetEncoding
    messageHeadersSetEncoding               ,


-- ** messageHeadersSetExpectations
    messageHeadersSetExpectations           ,


-- ** messageHeadersSetRange
    messageHeadersSetRange                  ,


-- ** messageHeadersSetRanges
    messageHeadersSetRanges                 ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Soup.Types
import GI.Soup.Callbacks

newtype MessageHeaders = MessageHeaders (ForeignPtr MessageHeaders)
foreign import ccall "soup_message_headers_get_type" c_soup_message_headers_get_type :: 
    IO GType

instance BoxedObject MessageHeaders where
    boxedType _ = c_soup_message_headers_get_type

noMessageHeaders :: Maybe MessageHeaders
noMessageHeaders = Nothing

-- method MessageHeaders::new
-- method type : Constructor
-- Args : [Arg {argName = "type", argType = TInterface "Soup" "MessageHeadersType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "type", argType = TInterface "Soup" "MessageHeadersType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Soup" "MessageHeaders"
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_new" soup_message_headers_new :: 
    CUInt ->                                -- type : TInterface "Soup" "MessageHeadersType"
    IO (Ptr MessageHeaders)


messageHeadersNew ::
    (MonadIO m) =>
    MessageHeadersType ->                   -- type
    m MessageHeaders
messageHeadersNew type_ = liftIO $ do
    let type_' = (fromIntegral . fromEnum) type_
    result <- soup_message_headers_new type_'
    checkUnexpectedReturnNULL "soup_message_headers_new" result
    result' <- (wrapBoxed MessageHeaders) result
    return result'

-- method MessageHeaders::append
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_append" soup_message_headers_append :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- value : TBasicType TUTF8
    IO ()


messageHeadersAppend ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    T.Text ->                               -- name
    T.Text ->                               -- value
    m ()
messageHeadersAppend _obj name value = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    name' <- textToCString name
    value' <- textToCString value
    soup_message_headers_append _obj' name' value'
    touchManagedPtr _obj
    freeMem name'
    freeMem value'
    return ()

-- method MessageHeaders::clean_connection_headers
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_clean_connection_headers" soup_message_headers_clean_connection_headers :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    IO ()


messageHeadersCleanConnectionHeaders ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    m ()
messageHeadersCleanConnectionHeaders _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    soup_message_headers_clean_connection_headers _obj'
    touchManagedPtr _obj
    return ()

-- method MessageHeaders::clear
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_clear" soup_message_headers_clear :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    IO ()


messageHeadersClear ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    m ()
messageHeadersClear _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    soup_message_headers_clear _obj'
    touchManagedPtr _obj
    return ()

-- method MessageHeaders::foreach
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TInterface "Soup" "MessageHeadersForeachFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeCall, argClosure = 2, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TInterface "Soup" "MessageHeadersForeachFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeCall, argClosure = 2, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_foreach" soup_message_headers_foreach :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    FunPtr MessageHeadersForeachFuncC ->    -- func : TInterface "Soup" "MessageHeadersForeachFunc"
    Ptr () ->                               -- user_data : TBasicType TVoid
    IO ()


messageHeadersForeach ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    MessageHeadersForeachFunc ->            -- func
    m ()
messageHeadersForeach _obj func = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    func' <- mkMessageHeadersForeachFunc (messageHeadersForeachFuncWrapper Nothing func)
    let user_data = nullPtr
    soup_message_headers_foreach _obj' func' user_data
    safeFreeFunPtr $ castFunPtrToPtr func'
    touchManagedPtr _obj
    return ()

-- method MessageHeaders::free
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_free" soup_message_headers_free :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    IO ()


messageHeadersFree ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    m ()
messageHeadersFree _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    soup_message_headers_free _obj'
    touchManagedPtr _obj
    return ()

-- method MessageHeaders::free_ranges
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ranges", argType = TInterface "Soup" "Range", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ranges", argType = TInterface "Soup" "Range", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_free_ranges" soup_message_headers_free_ranges :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    Ptr Range ->                            -- ranges : TInterface "Soup" "Range"
    IO ()


messageHeadersFreeRanges ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    Range ->                                -- ranges
    m ()
messageHeadersFreeRanges _obj ranges = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let ranges' = unsafeManagedPtrGetPtr ranges
    soup_message_headers_free_ranges _obj' ranges'
    touchManagedPtr _obj
    touchManagedPtr ranges
    return ()

-- method MessageHeaders::get
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_get" soup_message_headers_get :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    CString ->                              -- name : TBasicType TUTF8
    IO CString

{-# DEPRECATED messageHeadersGet ["Use soup_message_headers_get_one() or","soup_message_headers_get_list() instead."]#-}
messageHeadersGet ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    T.Text ->                               -- name
    m T.Text
messageHeadersGet _obj name = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    name' <- textToCString name
    result <- soup_message_headers_get _obj' name'
    checkUnexpectedReturnNULL "soup_message_headers_get" result
    result' <- cstringToText result
    touchManagedPtr _obj
    freeMem name'
    return result'

-- method MessageHeaders::get_content_disposition
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "disposition", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "params", argType = TGHash (TBasicType TUTF8) (TBasicType TUTF8), direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_get_content_disposition" soup_message_headers_get_content_disposition :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    Ptr CString ->                          -- disposition : TBasicType TUTF8
    Ptr (Ptr (GHashTable CString CString)) -> -- params : TGHash (TBasicType TUTF8) (TBasicType TUTF8)
    IO CInt


messageHeadersGetContentDisposition ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    m (Bool,T.Text,(Map.Map T.Text T.Text))
messageHeadersGetContentDisposition _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    disposition <- allocMem :: IO (Ptr CString)
    params <- allocMem :: IO (Ptr (Ptr (GHashTable CString CString)))
    result <- soup_message_headers_get_content_disposition _obj' disposition params
    let result' = (/= 0) result
    disposition' <- peek disposition
    disposition'' <- cstringToText disposition'
    freeMem disposition'
    params' <- peek params
    params'' <- unpackGHashTable params'
    let params''' = mapFirst cstringUnpackPtr params''
    params'''' <- mapFirstA cstringToText params'''
    let params''''' = mapSecond cstringUnpackPtr params''''
    params'''''' <- mapSecondA cstringToText params'''''
    let params''''''' = Map.fromList params''''''
    unrefGHashTable params'
    touchManagedPtr _obj
    freeMem disposition
    freeMem params
    return (result', disposition'', params''''''')

-- method MessageHeaders::get_content_length
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt64
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_get_content_length" soup_message_headers_get_content_length :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    IO Int64


messageHeadersGetContentLength ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    m Int64
messageHeadersGetContentLength _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- soup_message_headers_get_content_length _obj'
    touchManagedPtr _obj
    return result

-- method MessageHeaders::get_content_range
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "start", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "total_length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "start", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "total_length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_get_content_range" soup_message_headers_get_content_range :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    Int64 ->                                -- start : TBasicType TInt64
    Int64 ->                                -- end : TBasicType TInt64
    Int64 ->                                -- total_length : TBasicType TInt64
    IO CInt


messageHeadersGetContentRange ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    Int64 ->                                -- start
    Int64 ->                                -- end
    Int64 ->                                -- total_length
    m Bool
messageHeadersGetContentRange _obj start end total_length = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- soup_message_headers_get_content_range _obj' start end total_length
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method MessageHeaders::get_content_type
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "params", argType = TGHash (TBasicType TUTF8) (TBasicType TUTF8), direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_get_content_type" soup_message_headers_get_content_type :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    Ptr (Ptr (GHashTable CString CString)) -> -- params : TGHash (TBasicType TUTF8) (TBasicType TUTF8)
    IO CString


messageHeadersGetContentType ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    m (T.Text,(Map.Map T.Text T.Text))
messageHeadersGetContentType _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    params <- allocMem :: IO (Ptr (Ptr (GHashTable CString CString)))
    result <- soup_message_headers_get_content_type _obj' params
    checkUnexpectedReturnNULL "soup_message_headers_get_content_type" result
    result' <- cstringToText result
    params' <- peek params
    params'' <- unpackGHashTable params'
    let params''' = mapFirst cstringUnpackPtr params''
    params'''' <- mapFirstA cstringToText params'''
    let params''''' = mapSecond cstringUnpackPtr params''''
    params'''''' <- mapSecondA cstringToText params'''''
    let params''''''' = Map.fromList params''''''
    unrefGHashTable params'
    touchManagedPtr _obj
    freeMem params
    return (result', params''''''')

-- method MessageHeaders::get_encoding
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Soup" "Encoding"
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_get_encoding" soup_message_headers_get_encoding :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    IO CUInt


messageHeadersGetEncoding ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    m Encoding
messageHeadersGetEncoding _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- soup_message_headers_get_encoding _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

-- method MessageHeaders::get_expectations
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Soup" "Expectation"
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_get_expectations" soup_message_headers_get_expectations :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    IO CUInt


messageHeadersGetExpectations ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    m [Expectation]
messageHeadersGetExpectations _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- soup_message_headers_get_expectations _obj'
    let result' = wordToGFlags result
    touchManagedPtr _obj
    return result'

-- method MessageHeaders::get_headers_type
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Soup" "MessageHeadersType"
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_get_headers_type" soup_message_headers_get_headers_type :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    IO CUInt


messageHeadersGetHeadersType ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    m MessageHeadersType
messageHeadersGetHeadersType _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- soup_message_headers_get_headers_type _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

-- method MessageHeaders::get_list
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_get_list" soup_message_headers_get_list :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    CString ->                              -- name : TBasicType TUTF8
    IO CString


messageHeadersGetList ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    T.Text ->                               -- name
    m T.Text
messageHeadersGetList _obj name = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    name' <- textToCString name
    result <- soup_message_headers_get_list _obj' name'
    checkUnexpectedReturnNULL "soup_message_headers_get_list" result
    result' <- cstringToText result
    touchManagedPtr _obj
    freeMem name'
    return result'

-- method MessageHeaders::get_one
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_get_one" soup_message_headers_get_one :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    CString ->                              -- name : TBasicType TUTF8
    IO CString


messageHeadersGetOne ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    T.Text ->                               -- name
    m T.Text
messageHeadersGetOne _obj name = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    name' <- textToCString name
    result <- soup_message_headers_get_one _obj' name'
    checkUnexpectedReturnNULL "soup_message_headers_get_one" result
    result' <- cstringToText result
    touchManagedPtr _obj
    freeMem name'
    return result'

-- method MessageHeaders::get_ranges
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "total_length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ranges", argType = TCArray False (-1) 3 (TInterface "Soup" "Range"), direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "length", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : [Arg {argName = "length", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "total_length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_get_ranges" soup_message_headers_get_ranges :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    Int64 ->                                -- total_length : TBasicType TInt64
    Ptr (Ptr Range) ->                      -- ranges : TCArray False (-1) 3 (TInterface "Soup" "Range")
    Ptr Int32 ->                            -- length : TBasicType TInt32
    IO CInt


messageHeadersGetRanges ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    Int64 ->                                -- total_length
    m (Bool,[Range])
messageHeadersGetRanges _obj total_length = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    ranges <- allocMem :: IO (Ptr (Ptr Range))
    length_ <- allocMem :: IO (Ptr Int32)
    result <- soup_message_headers_get_ranges _obj' total_length ranges length_
    length_' <- peek length_
    let result' = (/= 0) result
    ranges' <- peek ranges
    ranges'' <- (unpackBlockArrayWithLength 16 length_') ranges'
    ranges''' <- mapM (wrapPtr Range) ranges''
    freeMem ranges'
    touchManagedPtr _obj
    freeMem ranges
    freeMem length_
    return (result', ranges''')

-- method MessageHeaders::header_contains
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "token", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "token", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_header_contains" soup_message_headers_header_contains :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- token : TBasicType TUTF8
    IO CInt


messageHeadersHeaderContains ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    T.Text ->                               -- name
    T.Text ->                               -- token
    m Bool
messageHeadersHeaderContains _obj name token = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    name' <- textToCString name
    token' <- textToCString token
    result <- soup_message_headers_header_contains _obj' name' token'
    let result' = (/= 0) result
    touchManagedPtr _obj
    freeMem name'
    freeMem token'
    return result'

-- method MessageHeaders::header_equals
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_header_equals" soup_message_headers_header_equals :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- value : TBasicType TUTF8
    IO CInt


messageHeadersHeaderEquals ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    T.Text ->                               -- name
    T.Text ->                               -- value
    m Bool
messageHeadersHeaderEquals _obj name value = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    name' <- textToCString name
    value' <- textToCString value
    result <- soup_message_headers_header_equals _obj' name' value'
    let result' = (/= 0) result
    touchManagedPtr _obj
    freeMem name'
    freeMem value'
    return result'

-- method MessageHeaders::remove
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_remove" soup_message_headers_remove :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    CString ->                              -- name : TBasicType TUTF8
    IO ()


messageHeadersRemove ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    T.Text ->                               -- name
    m ()
messageHeadersRemove _obj name = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    name' <- textToCString name
    soup_message_headers_remove _obj' name'
    touchManagedPtr _obj
    freeMem name'
    return ()

-- method MessageHeaders::replace
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_replace" soup_message_headers_replace :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- value : TBasicType TUTF8
    IO ()


messageHeadersReplace ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    T.Text ->                               -- name
    T.Text ->                               -- value
    m ()
messageHeadersReplace _obj name value = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    name' <- textToCString name
    value' <- textToCString value
    soup_message_headers_replace _obj' name' value'
    touchManagedPtr _obj
    freeMem name'
    freeMem value'
    return ()

-- method MessageHeaders::set_content_disposition
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "disposition", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "params", argType = TGHash (TBasicType TUTF8) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "disposition", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "params", argType = TGHash (TBasicType TUTF8) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_set_content_disposition" soup_message_headers_set_content_disposition :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    CString ->                              -- disposition : TBasicType TUTF8
    Ptr (GHashTable CString CString) ->     -- params : TGHash (TBasicType TUTF8) (TBasicType TUTF8)
    IO ()


messageHeadersSetContentDisposition ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    T.Text ->                               -- disposition
    Maybe (Map.Map T.Text T.Text) ->        -- params
    m ()
messageHeadersSetContentDisposition _obj disposition params = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    disposition' <- textToCString disposition
    maybeParams <- case params of
        Nothing -> return nullPtr
        Just jParams -> do
            let jParams' = Map.toList jParams
            jParams'' <- mapFirstA textToCString jParams'
            jParams''' <- mapSecondA textToCString jParams''
            let jParams'''' = mapFirst cstringPackPtr jParams'''
            let jParams''''' = mapSecond cstringPackPtr jParams''''
            jParams'''''' <- packGHashTable gStrHash gStrEqual (Just ptr_to_g_free) (Just ptr_to_g_free) jParams'''''
            return jParams''''''
    soup_message_headers_set_content_disposition _obj' disposition' maybeParams
    touchManagedPtr _obj
    freeMem disposition'
    unrefGHashTable maybeParams
    return ()

-- method MessageHeaders::set_content_length
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "content_length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "content_length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_set_content_length" soup_message_headers_set_content_length :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    Int64 ->                                -- content_length : TBasicType TInt64
    IO ()


messageHeadersSetContentLength ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    Int64 ->                                -- content_length
    m ()
messageHeadersSetContentLength _obj content_length = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    soup_message_headers_set_content_length _obj' content_length
    touchManagedPtr _obj
    return ()

-- method MessageHeaders::set_content_range
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "start", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "total_length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "start", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "total_length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_set_content_range" soup_message_headers_set_content_range :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    Int64 ->                                -- start : TBasicType TInt64
    Int64 ->                                -- end : TBasicType TInt64
    Int64 ->                                -- total_length : TBasicType TInt64
    IO ()


messageHeadersSetContentRange ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    Int64 ->                                -- start
    Int64 ->                                -- end
    Int64 ->                                -- total_length
    m ()
messageHeadersSetContentRange _obj start end total_length = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    soup_message_headers_set_content_range _obj' start end total_length
    touchManagedPtr _obj
    return ()

-- method MessageHeaders::set_content_type
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "content_type", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "params", argType = TGHash (TBasicType TUTF8) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "content_type", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "params", argType = TGHash (TBasicType TUTF8) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_set_content_type" soup_message_headers_set_content_type :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    CString ->                              -- content_type : TBasicType TUTF8
    Ptr (GHashTable CString CString) ->     -- params : TGHash (TBasicType TUTF8) (TBasicType TUTF8)
    IO ()


messageHeadersSetContentType ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    T.Text ->                               -- content_type
    Maybe (Map.Map T.Text T.Text) ->        -- params
    m ()
messageHeadersSetContentType _obj content_type params = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    content_type' <- textToCString content_type
    maybeParams <- case params of
        Nothing -> return nullPtr
        Just jParams -> do
            let jParams' = Map.toList jParams
            jParams'' <- mapFirstA textToCString jParams'
            jParams''' <- mapSecondA textToCString jParams''
            let jParams'''' = mapFirst cstringPackPtr jParams'''
            let jParams''''' = mapSecond cstringPackPtr jParams''''
            jParams'''''' <- packGHashTable gStrHash gStrEqual (Just ptr_to_g_free) (Just ptr_to_g_free) jParams'''''
            return jParams''''''
    soup_message_headers_set_content_type _obj' content_type' maybeParams
    touchManagedPtr _obj
    freeMem content_type'
    unrefGHashTable maybeParams
    return ()

-- method MessageHeaders::set_encoding
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "encoding", argType = TInterface "Soup" "Encoding", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "encoding", argType = TInterface "Soup" "Encoding", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_set_encoding" soup_message_headers_set_encoding :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    CUInt ->                                -- encoding : TInterface "Soup" "Encoding"
    IO ()


messageHeadersSetEncoding ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    Encoding ->                             -- encoding
    m ()
messageHeadersSetEncoding _obj encoding = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let encoding' = (fromIntegral . fromEnum) encoding
    soup_message_headers_set_encoding _obj' encoding'
    touchManagedPtr _obj
    return ()

-- method MessageHeaders::set_expectations
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "expectations", argType = TInterface "Soup" "Expectation", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "expectations", argType = TInterface "Soup" "Expectation", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_set_expectations" soup_message_headers_set_expectations :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    CUInt ->                                -- expectations : TInterface "Soup" "Expectation"
    IO ()


messageHeadersSetExpectations ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    [Expectation] ->                        -- expectations
    m ()
messageHeadersSetExpectations _obj expectations = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let expectations' = gflagsToWord expectations
    soup_message_headers_set_expectations _obj' expectations'
    touchManagedPtr _obj
    return ()

-- method MessageHeaders::set_range
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "start", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "start", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_set_range" soup_message_headers_set_range :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    Int64 ->                                -- start : TBasicType TInt64
    Int64 ->                                -- end : TBasicType TInt64
    IO ()


messageHeadersSetRange ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    Int64 ->                                -- start
    Int64 ->                                -- end
    m ()
messageHeadersSetRange _obj start end = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    soup_message_headers_set_range _obj' start end
    touchManagedPtr _obj
    return ()

-- method MessageHeaders::set_ranges
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ranges", argType = TInterface "Soup" "Range", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ranges", argType = TInterface "Soup" "Range", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "soup_message_headers_set_ranges" soup_message_headers_set_ranges :: 
    Ptr MessageHeaders ->                   -- _obj : TInterface "Soup" "MessageHeaders"
    Ptr Range ->                            -- ranges : TInterface "Soup" "Range"
    Int32 ->                                -- length : TBasicType TInt32
    IO ()


messageHeadersSetRanges ::
    (MonadIO m) =>
    MessageHeaders ->                       -- _obj
    Range ->                                -- ranges
    Int32 ->                                -- length
    m ()
messageHeadersSetRanges _obj ranges length_ = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let ranges' = unsafeManagedPtrGetPtr ranges
    soup_message_headers_set_ranges _obj' ranges' length_
    touchManagedPtr _obj
    touchManagedPtr ranges
    return ()