-- Generated code. {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# LANGUAGE ForeignFunctionInterface, ConstraintKinds, TypeFamilies, MultiParamTypeClasses, KindSignatures, FlexibleInstances, UndecidableInstances, DataKinds, OverloadedStrings, NegativeLiterals, FlexibleContexts #-} module GI.Soup where import Prelude () import Data.GI.Base.ShortPrelude import Data.Char import Data.Int import Data.Word import qualified Data.ByteString.Char8 as B import Data.ByteString.Char8 (ByteString) import qualified Data.Map as Map import Foreign.C import Foreign.Ptr import Foreign.ForeignPtr import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr) import Foreign.Storable (peek, poke, sizeOf) import Control.Applicative ((<$>)) import Control.Exception (onException) import Control.Monad.IO.Class import qualified Data.Text as T import Data.GI.Base.Attributes hiding (get, set) import Data.GI.Base.BasicTypes import Data.GI.Base.BasicConversions import Data.GI.Base.Closure import Data.GI.Base.GError import Data.GI.Base.GHashTable import Data.GI.Base.GParamSpec import Data.GI.Base.GVariant import Data.GI.Base.GValue import Data.GI.Base.ManagedPtr import Data.GI.Base.Overloading import Data.GI.Base.Properties hiding (new) import Data.GI.Base.Signals (SignalConnectMode(..), connectSignalFunPtr, SignalHandlerId) import Data.GI.Base.Utils import qualified GI.GLib as GLib import qualified GI.GLibAttributes as GLibA import qualified GI.GObject as GObject import qualified GI.GObjectAttributes as GObjectA import qualified GI.Gio as Gio import qualified GI.GioAttributes as GioA -- object Address newtype Address = Address (ForeignPtr Address) noAddress :: Maybe Address noAddress = Nothing foreign import ccall "soup_address_get_type" c_soup_address_get_type :: IO GType type instance ParentTypes Address = '[GObject.Object, Gio.SocketConnectable] instance GObject Address where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_address_get_type class GObject o => AddressK o instance (GObject o, IsDescendantOf Address o) => AddressK o toAddress :: AddressK o => o -> IO Address toAddress = unsafeCastTo Address -- method Address::new -- method type : Constructor -- Args : [Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "port", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "port", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Address" -- throws : False -- Skip return : False foreign import ccall "soup_address_new" soup_address_new :: CString -> -- name : TBasicType TUTF8 Word32 -> -- port : TBasicType TUInt32 IO (Ptr Address) addressNew :: (MonadIO m) => T.Text -> -- name Word32 -> -- port m Address addressNew name port = liftIO $ do name' <- textToCString name result <- soup_address_new name' port checkUnexpectedReturnNULL "soup_address_new" result result' <- (wrapObject Address) result freeMem name' return result' -- method Address::new_any -- method type : Constructor -- Args : [Arg {argName = "family", argType = TInterface "Soup" "AddressFamily", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "port", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "family", argType = TInterface "Soup" "AddressFamily", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "port", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Address" -- throws : False -- Skip return : False foreign import ccall "soup_address_new_any" soup_address_new_any :: CUInt -> -- family : TInterface "Soup" "AddressFamily" Word32 -> -- port : TBasicType TUInt32 IO (Ptr Address) addressNewAny :: (MonadIO m) => AddressFamily -> -- family Word32 -> -- port m Address addressNewAny family port = liftIO $ do let family' = (fromIntegral . fromEnum) family result <- soup_address_new_any family' port checkUnexpectedReturnNULL "soup_address_new_any" result result' <- (wrapObject Address) result return result' -- method Address::new_from_sockaddr -- method type : Constructor -- Args : [Arg {argName = "sa", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "sa", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Address" -- throws : False -- Skip return : False foreign import ccall "soup_address_new_from_sockaddr" soup_address_new_from_sockaddr :: Ptr () -> -- sa : TBasicType TVoid Int32 -> -- len : TBasicType TInt32 IO (Ptr Address) addressNewFromSockaddr :: (MonadIO m) => Ptr () -> -- sa Int32 -> -- len m Address addressNewFromSockaddr sa len = liftIO $ do result <- soup_address_new_from_sockaddr sa len checkUnexpectedReturnNULL "soup_address_new_from_sockaddr" result result' <- (wrapObject Address) result return result' -- method Address::equal_by_ip -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "addr2", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "addr2", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_address_equal_by_ip" soup_address_equal_by_ip :: Ptr Address -> -- _obj : TInterface "Soup" "Address" Ptr Address -> -- addr2 : TInterface "Soup" "Address" IO CInt addressEqualByIp :: (MonadIO m, AddressK a, AddressK b) => a -> -- _obj b -> -- addr2 m Bool addressEqualByIp _obj addr2 = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let addr2' = unsafeManagedPtrCastPtr addr2 result <- soup_address_equal_by_ip _obj' addr2' let result' = (/= 0) result touchManagedPtr _obj touchManagedPtr addr2 return result' -- method Address::equal_by_name -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "addr2", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "addr2", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_address_equal_by_name" soup_address_equal_by_name :: Ptr Address -> -- _obj : TInterface "Soup" "Address" Ptr Address -> -- addr2 : TInterface "Soup" "Address" IO CInt addressEqualByName :: (MonadIO m, AddressK a, AddressK b) => a -> -- _obj b -> -- addr2 m Bool addressEqualByName _obj addr2 = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let addr2' = unsafeManagedPtrCastPtr addr2 result <- soup_address_equal_by_name _obj' addr2' let result' = (/= 0) result touchManagedPtr _obj touchManagedPtr addr2 return result' -- method Address::get_gsockaddr -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Gio" "SocketAddress" -- throws : False -- Skip return : False foreign import ccall "soup_address_get_gsockaddr" soup_address_get_gsockaddr :: Ptr Address -> -- _obj : TInterface "Soup" "Address" IO (Ptr Gio.SocketAddress) addressGetGsockaddr :: (MonadIO m, AddressK a) => a -> -- _obj m Gio.SocketAddress addressGetGsockaddr _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_address_get_gsockaddr _obj' checkUnexpectedReturnNULL "soup_address_get_gsockaddr" result result' <- (wrapObject Gio.SocketAddress) result touchManagedPtr _obj return result' -- method Address::get_name -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_address_get_name" soup_address_get_name :: Ptr Address -> -- _obj : TInterface "Soup" "Address" IO CString addressGetName :: (MonadIO m, AddressK a) => a -> -- _obj m T.Text addressGetName _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_address_get_name _obj' checkUnexpectedReturnNULL "soup_address_get_name" result result' <- cstringToText result touchManagedPtr _obj return result' -- method Address::get_physical -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_address_get_physical" soup_address_get_physical :: Ptr Address -> -- _obj : TInterface "Soup" "Address" IO CString addressGetPhysical :: (MonadIO m, AddressK a) => a -> -- _obj m T.Text addressGetPhysical _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_address_get_physical _obj' checkUnexpectedReturnNULL "soup_address_get_physical" result result' <- cstringToText result touchManagedPtr _obj return result' -- method Address::get_port -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_address_get_port" soup_address_get_port :: Ptr Address -> -- _obj : TInterface "Soup" "Address" IO Word32 addressGetPort :: (MonadIO m, AddressK a) => a -> -- _obj m Word32 addressGetPort _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_address_get_port _obj' touchManagedPtr _obj return result -- method Address::hash_by_ip -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_address_hash_by_ip" soup_address_hash_by_ip :: Ptr Address -> -- _obj : TInterface "Soup" "Address" IO Word32 addressHashByIp :: (MonadIO m, AddressK a) => a -> -- _obj m Word32 addressHashByIp _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_address_hash_by_ip _obj' touchManagedPtr _obj return result -- method Address::hash_by_name -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_address_hash_by_name" soup_address_hash_by_name :: Ptr Address -> -- _obj : TInterface "Soup" "Address" IO Word32 addressHashByName :: (MonadIO m, AddressK a) => a -> -- _obj m Word32 addressHashByName _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_address_hash_by_name _obj' touchManagedPtr _obj return result -- method Address::is_resolved -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_address_is_resolved" soup_address_is_resolved :: Ptr Address -> -- _obj : TInterface "Soup" "Address" IO CInt addressIsResolved :: (MonadIO m, AddressK a) => a -> -- _obj m Bool addressIsResolved _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_address_is_resolved _obj' let result' = (/= 0) result touchManagedPtr _obj return result' -- method Address::resolve_async -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "async_context", argType = TInterface "GLib" "MainContext", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "AddressCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = 4, 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" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "async_context", argType = TInterface "GLib" "MainContext", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "AddressCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = 4, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_address_resolve_async" soup_address_resolve_async :: Ptr Address -> -- _obj : TInterface "Soup" "Address" Ptr GLib.MainContext -> -- async_context : TInterface "GLib" "MainContext" Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" FunPtr AddressCallbackC -> -- callback : TInterface "Soup" "AddressCallback" Ptr () -> -- user_data : TBasicType TVoid IO () addressResolveAsync :: (MonadIO m, AddressK a, Gio.CancellableK b) => a -> -- _obj Maybe (GLib.MainContext) -> -- async_context Maybe (b) -> -- cancellable AddressCallback -> -- callback m () addressResolveAsync _obj async_context cancellable callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj maybeAsync_context <- case async_context of Nothing -> return nullPtr Just jAsync_context -> do let jAsync_context' = unsafeManagedPtrGetPtr jAsync_context return jAsync_context' maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' ptrcallback <- callocMem :: IO (Ptr (FunPtr AddressCallbackC)) callback' <- mkAddressCallback (addressCallbackWrapper (Just ptrcallback) callback) poke ptrcallback callback' let user_data = nullPtr soup_address_resolve_async _obj' maybeAsync_context maybeCancellable callback' user_data touchManagedPtr _obj whenJust async_context touchManagedPtr whenJust cancellable touchManagedPtr return () -- method Address::resolve_sync -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Address", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_address_resolve_sync" soup_address_resolve_sync :: Ptr Address -> -- _obj : TInterface "Soup" "Address" Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" IO Word32 addressResolveSync :: (MonadIO m, AddressK a, Gio.CancellableK b) => a -> -- _obj Maybe (b) -> -- cancellable m Word32 addressResolveSync _obj cancellable = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' result <- soup_address_resolve_sync _obj' maybeCancellable touchManagedPtr _obj whenJust cancellable touchManagedPtr return result -- callback AddressCallback addressCallbackClosure :: AddressCallback -> IO Closure addressCallbackClosure cb = newCClosure =<< mkAddressCallback wrapped where wrapped = addressCallbackWrapper Nothing cb type AddressCallbackC = Ptr Address -> Word32 -> Ptr () -> IO () foreign import ccall "wrapper" mkAddressCallback :: AddressCallbackC -> IO (FunPtr AddressCallbackC) type AddressCallback = Address -> Word32 -> IO () noAddressCallback :: Maybe AddressCallback noAddressCallback = Nothing addressCallbackWrapper :: Maybe (Ptr (FunPtr (AddressCallbackC))) -> AddressCallback -> Ptr Address -> Word32 -> Ptr () -> IO () addressCallbackWrapper funptrptr _cb addr status _ = do addr' <- (newObject Address) addr _cb addr' status maybeReleaseFunPtr funptrptr -- Enum AddressFamily data AddressFamily = AddressFamilyInvalid | AddressFamilyIpv4 | AddressFamilyIpv6 | AnotherAddressFamily Int deriving (Show, Eq) instance Enum AddressFamily where fromEnum AddressFamilyInvalid = -1 fromEnum AddressFamilyIpv4 = 2 fromEnum AddressFamilyIpv6 = 10 fromEnum (AnotherAddressFamily k) = k toEnum -1 = AddressFamilyInvalid toEnum 2 = AddressFamilyIpv4 toEnum 10 = AddressFamilyIpv6 toEnum k = AnotherAddressFamily k foreign import ccall "soup_address_family_get_type" c_soup_address_family_get_type :: IO GType instance BoxedEnum AddressFamily where boxedEnumType _ = c_soup_address_family_get_type -- object Auth newtype Auth = Auth (ForeignPtr Auth) noAuth :: Maybe Auth noAuth = Nothing foreign import ccall "soup_auth_get_type" c_soup_auth_get_type :: IO GType type instance ParentTypes Auth = '[GObject.Object] instance GObject Auth where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_auth_get_type class GObject o => AuthK o instance (GObject o, IsDescendantOf Auth o) => AuthK o toAuth :: AuthK o => o -> IO Auth toAuth = unsafeCastTo Auth -- method Auth::new -- method type : Constructor -- Args : [Arg {argName = "type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "auth_header", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "auth_header", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Auth" -- throws : False -- Skip return : False foreign import ccall "soup_auth_new" soup_auth_new :: CGType -> -- type : TBasicType TGType Ptr Message -> -- msg : TInterface "Soup" "Message" CString -> -- auth_header : TBasicType TUTF8 IO (Ptr Auth) authNew :: (MonadIO m, MessageK a) => GType -> -- type a -> -- msg T.Text -> -- auth_header m Auth authNew type_ msg auth_header = liftIO $ do let type_' = gtypeToCGType type_ let msg' = unsafeManagedPtrCastPtr msg auth_header' <- textToCString auth_header result <- soup_auth_new type_' msg' auth_header' checkUnexpectedReturnNULL "soup_auth_new" result result' <- (wrapObject Auth) result touchManagedPtr msg freeMem auth_header' return result' -- method Auth::authenticate -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "username", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "password", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "username", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "password", 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_auth_authenticate" soup_auth_authenticate :: Ptr Auth -> -- _obj : TInterface "Soup" "Auth" CString -> -- username : TBasicType TUTF8 CString -> -- password : TBasicType TUTF8 IO () authAuthenticate :: (MonadIO m, AuthK a) => a -> -- _obj T.Text -> -- username T.Text -> -- password m () authAuthenticate _obj username password = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj username' <- textToCString username password' <- textToCString password soup_auth_authenticate _obj' username' password' touchManagedPtr _obj freeMem username' freeMem password' return () -- method Auth::get_authorization -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_auth_get_authorization" soup_auth_get_authorization :: Ptr Auth -> -- _obj : TInterface "Soup" "Auth" Ptr Message -> -- msg : TInterface "Soup" "Message" IO CString authGetAuthorization :: (MonadIO m, AuthK a, MessageK b) => a -> -- _obj b -> -- msg m T.Text authGetAuthorization _obj msg = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg result <- soup_auth_get_authorization _obj' msg' checkUnexpectedReturnNULL "soup_auth_get_authorization" result result' <- cstringToText result freeMem result touchManagedPtr _obj touchManagedPtr msg return result' -- method Auth::get_host -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_auth_get_host" soup_auth_get_host :: Ptr Auth -> -- _obj : TInterface "Soup" "Auth" IO CString authGetHost :: (MonadIO m, AuthK a) => a -> -- _obj m T.Text authGetHost _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_auth_get_host _obj' checkUnexpectedReturnNULL "soup_auth_get_host" result result' <- cstringToText result touchManagedPtr _obj return result' -- method Auth::get_info -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_auth_get_info" soup_auth_get_info :: Ptr Auth -> -- _obj : TInterface "Soup" "Auth" IO CString authGetInfo :: (MonadIO m, AuthK a) => a -> -- _obj m T.Text authGetInfo _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_auth_get_info _obj' checkUnexpectedReturnNULL "soup_auth_get_info" result result' <- cstringToText result freeMem result touchManagedPtr _obj return result' -- method Auth::get_protection_space -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "source_uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "source_uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TGSList (TBasicType TUTF8) -- throws : False -- Skip return : False foreign import ccall "soup_auth_get_protection_space" soup_auth_get_protection_space :: Ptr Auth -> -- _obj : TInterface "Soup" "Auth" Ptr URI -> -- source_uri : TInterface "Soup" "URI" IO (Ptr (GSList CString)) authGetProtectionSpace :: (MonadIO m, AuthK a) => a -> -- _obj URI -> -- source_uri m [T.Text] authGetProtectionSpace _obj source_uri = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let source_uri' = unsafeManagedPtrGetPtr source_uri result <- soup_auth_get_protection_space _obj' source_uri' checkUnexpectedReturnNULL "soup_auth_get_protection_space" result result' <- unpackGSList result result'' <- mapM cstringToText result' mapGSList freeMem result g_slist_free result touchManagedPtr _obj touchManagedPtr source_uri return result'' -- method Auth::get_realm -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_auth_get_realm" soup_auth_get_realm :: Ptr Auth -> -- _obj : TInterface "Soup" "Auth" IO CString authGetRealm :: (MonadIO m, AuthK a) => a -> -- _obj m T.Text authGetRealm _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_auth_get_realm _obj' checkUnexpectedReturnNULL "soup_auth_get_realm" result result' <- cstringToText result touchManagedPtr _obj return result' -- method Auth::get_saved_password -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user", 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_auth_get_saved_password" soup_auth_get_saved_password :: Ptr Auth -> -- _obj : TInterface "Soup" "Auth" CString -> -- user : TBasicType TUTF8 IO CString authGetSavedPassword :: (MonadIO m, AuthK a) => a -> -- _obj T.Text -> -- user m T.Text authGetSavedPassword _obj user = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj user' <- textToCString user result <- soup_auth_get_saved_password _obj' user' checkUnexpectedReturnNULL "soup_auth_get_saved_password" result result' <- cstringToText result touchManagedPtr _obj freeMem user' return result' -- method Auth::get_saved_users -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TGSList (TBasicType TUTF8) -- throws : False -- Skip return : False foreign import ccall "soup_auth_get_saved_users" soup_auth_get_saved_users :: Ptr Auth -> -- _obj : TInterface "Soup" "Auth" IO (Ptr (GSList CString)) authGetSavedUsers :: (MonadIO m, AuthK a) => a -> -- _obj m [T.Text] authGetSavedUsers _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_auth_get_saved_users _obj' checkUnexpectedReturnNULL "soup_auth_get_saved_users" result result' <- unpackGSList result result'' <- mapM cstringToText result' mapGSList freeMem result g_slist_free result touchManagedPtr _obj return result'' -- method Auth::get_scheme_name -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_auth_get_scheme_name" soup_auth_get_scheme_name :: Ptr Auth -> -- _obj : TInterface "Soup" "Auth" IO CString authGetSchemeName :: (MonadIO m, AuthK a) => a -> -- _obj m T.Text authGetSchemeName _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_auth_get_scheme_name _obj' checkUnexpectedReturnNULL "soup_auth_get_scheme_name" result result' <- cstringToText result touchManagedPtr _obj return result' -- method Auth::has_saved_password -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "username", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "password", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "username", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "password", 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_auth_has_saved_password" soup_auth_has_saved_password :: Ptr Auth -> -- _obj : TInterface "Soup" "Auth" CString -> -- username : TBasicType TUTF8 CString -> -- password : TBasicType TUTF8 IO () authHasSavedPassword :: (MonadIO m, AuthK a) => a -> -- _obj T.Text -> -- username T.Text -> -- password m () authHasSavedPassword _obj username password = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj username' <- textToCString username password' <- textToCString password soup_auth_has_saved_password _obj' username' password' touchManagedPtr _obj freeMem username' freeMem password' return () -- method Auth::is_authenticated -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_auth_is_authenticated" soup_auth_is_authenticated :: Ptr Auth -> -- _obj : TInterface "Soup" "Auth" IO CInt authIsAuthenticated :: (MonadIO m, AuthK a) => a -> -- _obj m Bool authIsAuthenticated _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_auth_is_authenticated _obj' let result' = (/= 0) result touchManagedPtr _obj return result' -- method Auth::is_for_proxy -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_auth_is_for_proxy" soup_auth_is_for_proxy :: Ptr Auth -> -- _obj : TInterface "Soup" "Auth" IO CInt authIsForProxy :: (MonadIO m, AuthK a) => a -> -- _obj m Bool authIsForProxy _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_auth_is_for_proxy _obj' let result' = (/= 0) result touchManagedPtr _obj return result' -- method Auth::is_ready -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_auth_is_ready" soup_auth_is_ready :: Ptr Auth -> -- _obj : TInterface "Soup" "Auth" Ptr Message -> -- msg : TInterface "Soup" "Message" IO CInt authIsReady :: (MonadIO m, AuthK a, MessageK b) => a -> -- _obj b -> -- msg m Bool authIsReady _obj msg = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg result <- soup_auth_is_ready _obj' msg' let result' = (/= 0) result touchManagedPtr _obj touchManagedPtr msg return result' -- method Auth::save_password -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "username", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "password", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "username", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "password", 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_auth_save_password" soup_auth_save_password :: Ptr Auth -> -- _obj : TInterface "Soup" "Auth" CString -> -- username : TBasicType TUTF8 CString -> -- password : TBasicType TUTF8 IO () authSavePassword :: (MonadIO m, AuthK a) => a -> -- _obj T.Text -> -- username T.Text -> -- password m () authSavePassword _obj username password = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj username' <- textToCString username password' <- textToCString password soup_auth_save_password _obj' username' password' touchManagedPtr _obj freeMem username' freeMem password' return () -- method Auth::update -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "auth_header", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "auth_header", 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_auth_update" soup_auth_update :: Ptr Auth -> -- _obj : TInterface "Soup" "Auth" Ptr Message -> -- msg : TInterface "Soup" "Message" CString -> -- auth_header : TBasicType TUTF8 IO CInt authUpdate :: (MonadIO m, AuthK a, MessageK b) => a -> -- _obj b -> -- msg T.Text -> -- auth_header m Bool authUpdate _obj msg auth_header = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg auth_header' <- textToCString auth_header result <- soup_auth_update _obj' msg' auth_header' let result' = (/= 0) result touchManagedPtr _obj touchManagedPtr msg freeMem auth_header' return result' -- object AuthBasic newtype AuthBasic = AuthBasic (ForeignPtr AuthBasic) noAuthBasic :: Maybe AuthBasic noAuthBasic = Nothing foreign import ccall "soup_auth_basic_get_type" c_soup_auth_basic_get_type :: IO GType type instance ParentTypes AuthBasic = '[Auth, GObject.Object] instance GObject AuthBasic where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_auth_basic_get_type class GObject o => AuthBasicK o instance (GObject o, IsDescendantOf AuthBasic o) => AuthBasicK o toAuthBasic :: AuthBasicK o => o -> IO AuthBasic toAuthBasic = unsafeCastTo AuthBasic -- object AuthDigest newtype AuthDigest = AuthDigest (ForeignPtr AuthDigest) noAuthDigest :: Maybe AuthDigest noAuthDigest = Nothing foreign import ccall "soup_auth_digest_get_type" c_soup_auth_digest_get_type :: IO GType type instance ParentTypes AuthDigest = '[Auth, GObject.Object] instance GObject AuthDigest where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_auth_digest_get_type class GObject o => AuthDigestK o instance (GObject o, IsDescendantOf AuthDigest o) => AuthDigestK o toAuthDigest :: AuthDigestK o => o -> IO AuthDigest toAuthDigest = unsafeCastTo AuthDigest -- object AuthDomain newtype AuthDomain = AuthDomain (ForeignPtr AuthDomain) noAuthDomain :: Maybe AuthDomain noAuthDomain = Nothing foreign import ccall "soup_auth_domain_get_type" c_soup_auth_domain_get_type :: IO GType type instance ParentTypes AuthDomain = '[GObject.Object] instance GObject AuthDomain where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_auth_domain_get_type class GObject o => AuthDomainK o instance (GObject o, IsDescendantOf AuthDomain o) => AuthDomainK o toAuthDomain :: AuthDomainK o => o -> IO AuthDomain toAuthDomain = unsafeCastTo AuthDomain -- method AuthDomain::accepts -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_auth_domain_accepts" soup_auth_domain_accepts :: Ptr AuthDomain -> -- _obj : TInterface "Soup" "AuthDomain" Ptr Message -> -- msg : TInterface "Soup" "Message" IO CString authDomainAccepts :: (MonadIO m, AuthDomainK a, MessageK b) => a -> -- _obj b -> -- msg m T.Text authDomainAccepts _obj msg = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg result <- soup_auth_domain_accepts _obj' msg' checkUnexpectedReturnNULL "soup_auth_domain_accepts" result result' <- cstringToText result freeMem result touchManagedPtr _obj touchManagedPtr msg return result' -- method AuthDomain::add_path -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", 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_auth_domain_add_path" soup_auth_domain_add_path :: Ptr AuthDomain -> -- _obj : TInterface "Soup" "AuthDomain" CString -> -- path : TBasicType TUTF8 IO () authDomainAddPath :: (MonadIO m, AuthDomainK a) => a -> -- _obj T.Text -> -- path m () authDomainAddPath _obj path = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj path' <- textToCString path soup_auth_domain_add_path _obj' path' touchManagedPtr _obj freeMem path' return () -- method AuthDomain::basic_set_auth_callback -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "AuthDomainBasicAuthCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dnotify", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "AuthDomainBasicAuthCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_auth_domain_basic_set_auth_callback" soup_auth_domain_basic_set_auth_callback :: Ptr AuthDomain -> -- _obj : TInterface "Soup" "AuthDomain" FunPtr AuthDomainBasicAuthCallbackC -> -- callback : TInterface "Soup" "AuthDomainBasicAuthCallback" Ptr () -> -- user_data : TBasicType TVoid FunPtr GLib.DestroyNotifyC -> -- dnotify : TInterface "GLib" "DestroyNotify" IO () authDomainBasicSetAuthCallback :: (MonadIO m, AuthDomainK a) => a -> -- _obj AuthDomainBasicAuthCallback -> -- callback m () authDomainBasicSetAuthCallback _obj callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj callback' <- mkAuthDomainBasicAuthCallback (authDomainBasicAuthCallbackWrapper Nothing callback) let user_data = castFunPtrToPtr callback' let dnotify = safeFreeFunPtrPtr soup_auth_domain_basic_set_auth_callback _obj' callback' user_data dnotify touchManagedPtr _obj return () -- method AuthDomain::challenge -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_auth_domain_challenge" soup_auth_domain_challenge :: Ptr AuthDomain -> -- _obj : TInterface "Soup" "AuthDomain" Ptr Message -> -- msg : TInterface "Soup" "Message" IO () authDomainChallenge :: (MonadIO m, AuthDomainK a, MessageK b) => a -> -- _obj b -> -- msg m () authDomainChallenge _obj msg = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg soup_auth_domain_challenge _obj' msg' touchManagedPtr _obj touchManagedPtr msg return () -- method AuthDomain::check_password -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "username", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "password", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "username", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "password", 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_auth_domain_check_password" soup_auth_domain_check_password :: Ptr AuthDomain -> -- _obj : TInterface "Soup" "AuthDomain" Ptr Message -> -- msg : TInterface "Soup" "Message" CString -> -- username : TBasicType TUTF8 CString -> -- password : TBasicType TUTF8 IO CInt authDomainCheckPassword :: (MonadIO m, AuthDomainK a, MessageK b) => a -> -- _obj b -> -- msg T.Text -> -- username T.Text -> -- password m Bool authDomainCheckPassword _obj msg username password = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg username' <- textToCString username password' <- textToCString password result <- soup_auth_domain_check_password _obj' msg' username' password' let result' = (/= 0) result touchManagedPtr _obj touchManagedPtr msg freeMem username' freeMem password' return result' -- method AuthDomain::covers -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_auth_domain_covers" soup_auth_domain_covers :: Ptr AuthDomain -> -- _obj : TInterface "Soup" "AuthDomain" Ptr Message -> -- msg : TInterface "Soup" "Message" IO CInt authDomainCovers :: (MonadIO m, AuthDomainK a, MessageK b) => a -> -- _obj b -> -- msg m Bool authDomainCovers _obj msg = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg result <- soup_auth_domain_covers _obj' msg' let result' = (/= 0) result touchManagedPtr _obj touchManagedPtr msg return result' -- method AuthDomain::digest_set_auth_callback -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "AuthDomainDigestAuthCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dnotify", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "AuthDomainDigestAuthCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_auth_domain_digest_set_auth_callback" soup_auth_domain_digest_set_auth_callback :: Ptr AuthDomain -> -- _obj : TInterface "Soup" "AuthDomain" FunPtr AuthDomainDigestAuthCallbackC -> -- callback : TInterface "Soup" "AuthDomainDigestAuthCallback" Ptr () -> -- user_data : TBasicType TVoid FunPtr GLib.DestroyNotifyC -> -- dnotify : TInterface "GLib" "DestroyNotify" IO () authDomainDigestSetAuthCallback :: (MonadIO m, AuthDomainK a) => a -> -- _obj AuthDomainDigestAuthCallback -> -- callback m () authDomainDigestSetAuthCallback _obj callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj callback' <- mkAuthDomainDigestAuthCallback (authDomainDigestAuthCallbackWrapper Nothing callback) let user_data = castFunPtrToPtr callback' let dnotify = safeFreeFunPtrPtr soup_auth_domain_digest_set_auth_callback _obj' callback' user_data dnotify touchManagedPtr _obj return () -- method AuthDomain::get_realm -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_auth_domain_get_realm" soup_auth_domain_get_realm :: Ptr AuthDomain -> -- _obj : TInterface "Soup" "AuthDomain" IO CString authDomainGetRealm :: (MonadIO m, AuthDomainK a) => a -> -- _obj m T.Text authDomainGetRealm _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_auth_domain_get_realm _obj' checkUnexpectedReturnNULL "soup_auth_domain_get_realm" result result' <- cstringToText result touchManagedPtr _obj return result' -- method AuthDomain::remove_path -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", 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_auth_domain_remove_path" soup_auth_domain_remove_path :: Ptr AuthDomain -> -- _obj : TInterface "Soup" "AuthDomain" CString -> -- path : TBasicType TUTF8 IO () authDomainRemovePath :: (MonadIO m, AuthDomainK a) => a -> -- _obj T.Text -> -- path m () authDomainRemovePath _obj path = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj path' <- textToCString path soup_auth_domain_remove_path _obj' path' touchManagedPtr _obj freeMem path' return () -- method AuthDomain::set_filter -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "filter", argType = TInterface "Soup" "AuthDomainFilter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing},Arg {argName = "filter_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dnotify", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "filter", argType = TInterface "Soup" "AuthDomainFilter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_auth_domain_set_filter" soup_auth_domain_set_filter :: Ptr AuthDomain -> -- _obj : TInterface "Soup" "AuthDomain" FunPtr AuthDomainFilterC -> -- filter : TInterface "Soup" "AuthDomainFilter" Ptr () -> -- filter_data : TBasicType TVoid FunPtr GLib.DestroyNotifyC -> -- dnotify : TInterface "GLib" "DestroyNotify" IO () authDomainSetFilter :: (MonadIO m, AuthDomainK a) => a -> -- _obj AuthDomainFilter -> -- filter m () authDomainSetFilter _obj filter = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj filter' <- mkAuthDomainFilter (authDomainFilterWrapper Nothing filter) let filter_data = castFunPtrToPtr filter' let dnotify = safeFreeFunPtrPtr soup_auth_domain_set_filter _obj' filter' filter_data dnotify touchManagedPtr _obj return () -- method AuthDomain::set_generic_auth_callback -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "auth_callback", argType = TInterface "Soup" "AuthDomainGenericAuthCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing},Arg {argName = "auth_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dnotify", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "auth_callback", argType = TInterface "Soup" "AuthDomainGenericAuthCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_auth_domain_set_generic_auth_callback" soup_auth_domain_set_generic_auth_callback :: Ptr AuthDomain -> -- _obj : TInterface "Soup" "AuthDomain" FunPtr AuthDomainGenericAuthCallbackC -> -- auth_callback : TInterface "Soup" "AuthDomainGenericAuthCallback" Ptr () -> -- auth_data : TBasicType TVoid FunPtr GLib.DestroyNotifyC -> -- dnotify : TInterface "GLib" "DestroyNotify" IO () authDomainSetGenericAuthCallback :: (MonadIO m, AuthDomainK a) => a -> -- _obj AuthDomainGenericAuthCallback -> -- auth_callback m () authDomainSetGenericAuthCallback _obj auth_callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj auth_callback' <- mkAuthDomainGenericAuthCallback (authDomainGenericAuthCallbackWrapper Nothing auth_callback) let auth_data = castFunPtrToPtr auth_callback' let dnotify = safeFreeFunPtrPtr soup_auth_domain_set_generic_auth_callback _obj' auth_callback' auth_data dnotify touchManagedPtr _obj return () -- method AuthDomain::try_generic_auth_callback -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "username", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "username", 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_auth_domain_try_generic_auth_callback" soup_auth_domain_try_generic_auth_callback :: Ptr AuthDomain -> -- _obj : TInterface "Soup" "AuthDomain" Ptr Message -> -- msg : TInterface "Soup" "Message" CString -> -- username : TBasicType TUTF8 IO CInt authDomainTryGenericAuthCallback :: (MonadIO m, AuthDomainK a, MessageK b) => a -> -- _obj b -> -- msg T.Text -> -- username m Bool authDomainTryGenericAuthCallback _obj msg username = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg username' <- textToCString username result <- soup_auth_domain_try_generic_auth_callback _obj' msg' username' let result' = (/= 0) result touchManagedPtr _obj touchManagedPtr msg freeMem username' return result' -- object AuthDomainBasic newtype AuthDomainBasic = AuthDomainBasic (ForeignPtr AuthDomainBasic) noAuthDomainBasic :: Maybe AuthDomainBasic noAuthDomainBasic = Nothing foreign import ccall "soup_auth_domain_basic_get_type" c_soup_auth_domain_basic_get_type :: IO GType type instance ParentTypes AuthDomainBasic = '[AuthDomain, GObject.Object] instance GObject AuthDomainBasic where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_auth_domain_basic_get_type class GObject o => AuthDomainBasicK o instance (GObject o, IsDescendantOf AuthDomainBasic o) => AuthDomainBasicK o toAuthDomainBasic :: AuthDomainBasicK o => o -> IO AuthDomainBasic toAuthDomainBasic = unsafeCastTo AuthDomainBasic -- callback AuthDomainBasicAuthCallback authDomainBasicAuthCallbackClosure :: AuthDomainBasicAuthCallback -> IO Closure authDomainBasicAuthCallbackClosure cb = newCClosure =<< mkAuthDomainBasicAuthCallback wrapped where wrapped = authDomainBasicAuthCallbackWrapper Nothing cb type AuthDomainBasicAuthCallbackC = Ptr AuthDomain -> Ptr Message -> CString -> CString -> Ptr () -> IO CInt foreign import ccall "wrapper" mkAuthDomainBasicAuthCallback :: AuthDomainBasicAuthCallbackC -> IO (FunPtr AuthDomainBasicAuthCallbackC) type AuthDomainBasicAuthCallback = AuthDomain -> Message -> T.Text -> T.Text -> IO Bool noAuthDomainBasicAuthCallback :: Maybe AuthDomainBasicAuthCallback noAuthDomainBasicAuthCallback = Nothing authDomainBasicAuthCallbackWrapper :: Maybe (Ptr (FunPtr (AuthDomainBasicAuthCallbackC))) -> AuthDomainBasicAuthCallback -> Ptr AuthDomain -> Ptr Message -> CString -> CString -> Ptr () -> IO CInt authDomainBasicAuthCallbackWrapper funptrptr _cb domain msg username password _ = do domain' <- (newObject AuthDomain) domain msg' <- (newObject Message) msg username' <- cstringToText username password' <- cstringToText password result <- _cb domain' msg' username' password' maybeReleaseFunPtr funptrptr let result' = (fromIntegral . fromEnum) result return result' -- object AuthDomainDigest newtype AuthDomainDigest = AuthDomainDigest (ForeignPtr AuthDomainDigest) noAuthDomainDigest :: Maybe AuthDomainDigest noAuthDomainDigest = Nothing foreign import ccall "soup_auth_domain_digest_get_type" c_soup_auth_domain_digest_get_type :: IO GType type instance ParentTypes AuthDomainDigest = '[AuthDomain, GObject.Object] instance GObject AuthDomainDigest where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_auth_domain_digest_get_type class GObject o => AuthDomainDigestK o instance (GObject o, IsDescendantOf AuthDomainDigest o) => AuthDomainDigestK o toAuthDomainDigest :: AuthDomainDigestK o => o -> IO AuthDomainDigest toAuthDomainDigest = unsafeCastTo AuthDomainDigest -- method AuthDomainDigest::encode_password -- method type : MemberFunction -- Args : [Arg {argName = "username", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "realm", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "password", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "username", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "realm", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "password", 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_auth_domain_digest_encode_password" soup_auth_domain_digest_encode_password :: CString -> -- username : TBasicType TUTF8 CString -> -- realm : TBasicType TUTF8 CString -> -- password : TBasicType TUTF8 IO CString authDomainDigestEncodePassword :: (MonadIO m) => T.Text -> -- username T.Text -> -- realm T.Text -> -- password m T.Text authDomainDigestEncodePassword username realm password = liftIO $ do username' <- textToCString username realm' <- textToCString realm password' <- textToCString password result <- soup_auth_domain_digest_encode_password username' realm' password' checkUnexpectedReturnNULL "soup_auth_domain_digest_encode_password" result result' <- cstringToText result freeMem result freeMem username' freeMem realm' freeMem password' return result' -- callback AuthDomainDigestAuthCallback authDomainDigestAuthCallbackClosure :: AuthDomainDigestAuthCallback -> IO Closure authDomainDigestAuthCallbackClosure cb = newCClosure =<< mkAuthDomainDigestAuthCallback wrapped where wrapped = authDomainDigestAuthCallbackWrapper Nothing cb type AuthDomainDigestAuthCallbackC = Ptr AuthDomain -> Ptr Message -> CString -> Ptr () -> IO CString foreign import ccall "wrapper" mkAuthDomainDigestAuthCallback :: AuthDomainDigestAuthCallbackC -> IO (FunPtr AuthDomainDigestAuthCallbackC) type AuthDomainDigestAuthCallback = AuthDomain -> Message -> T.Text -> IO T.Text noAuthDomainDigestAuthCallback :: Maybe AuthDomainDigestAuthCallback noAuthDomainDigestAuthCallback = Nothing authDomainDigestAuthCallbackWrapper :: Maybe (Ptr (FunPtr (AuthDomainDigestAuthCallbackC))) -> AuthDomainDigestAuthCallback -> Ptr AuthDomain -> Ptr Message -> CString -> Ptr () -> IO CString authDomainDigestAuthCallbackWrapper funptrptr _cb domain msg username _ = do domain' <- (newObject AuthDomain) domain msg' <- (newObject Message) msg username' <- cstringToText username result <- _cb domain' msg' username' maybeReleaseFunPtr funptrptr result' <- textToCString result return result' -- callback AuthDomainFilter authDomainFilterClosure :: AuthDomainFilter -> IO Closure authDomainFilterClosure cb = newCClosure =<< mkAuthDomainFilter wrapped where wrapped = authDomainFilterWrapper Nothing cb type AuthDomainFilterC = Ptr AuthDomain -> Ptr Message -> Ptr () -> IO CInt foreign import ccall "wrapper" mkAuthDomainFilter :: AuthDomainFilterC -> IO (FunPtr AuthDomainFilterC) type AuthDomainFilter = AuthDomain -> Message -> IO Bool noAuthDomainFilter :: Maybe AuthDomainFilter noAuthDomainFilter = Nothing authDomainFilterWrapper :: Maybe (Ptr (FunPtr (AuthDomainFilterC))) -> AuthDomainFilter -> Ptr AuthDomain -> Ptr Message -> Ptr () -> IO CInt authDomainFilterWrapper funptrptr _cb domain msg _ = do domain' <- (newObject AuthDomain) domain msg' <- (newObject Message) msg result <- _cb domain' msg' maybeReleaseFunPtr funptrptr let result' = (fromIntegral . fromEnum) result return result' -- callback AuthDomainGenericAuthCallback authDomainGenericAuthCallbackClosure :: AuthDomainGenericAuthCallback -> IO Closure authDomainGenericAuthCallbackClosure cb = newCClosure =<< mkAuthDomainGenericAuthCallback wrapped where wrapped = authDomainGenericAuthCallbackWrapper Nothing cb type AuthDomainGenericAuthCallbackC = Ptr AuthDomain -> Ptr Message -> CString -> Ptr () -> IO CInt foreign import ccall "wrapper" mkAuthDomainGenericAuthCallback :: AuthDomainGenericAuthCallbackC -> IO (FunPtr AuthDomainGenericAuthCallbackC) type AuthDomainGenericAuthCallback = AuthDomain -> Message -> T.Text -> IO Bool noAuthDomainGenericAuthCallback :: Maybe AuthDomainGenericAuthCallback noAuthDomainGenericAuthCallback = Nothing authDomainGenericAuthCallbackWrapper :: Maybe (Ptr (FunPtr (AuthDomainGenericAuthCallbackC))) -> AuthDomainGenericAuthCallback -> Ptr AuthDomain -> Ptr Message -> CString -> Ptr () -> IO CInt authDomainGenericAuthCallbackWrapper funptrptr _cb domain msg username _ = do domain' <- (newObject AuthDomain) domain msg' <- (newObject Message) msg username' <- cstringToText username result <- _cb domain' msg' username' maybeReleaseFunPtr funptrptr let result' = (fromIntegral . fromEnum) result return result' -- object AuthManager newtype AuthManager = AuthManager (ForeignPtr AuthManager) noAuthManager :: Maybe AuthManager noAuthManager = Nothing foreign import ccall "soup_auth_manager_get_type" c_soup_auth_manager_get_type :: IO GType type instance ParentTypes AuthManager = '[GObject.Object, SessionFeature] instance GObject AuthManager where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_auth_manager_get_type class GObject o => AuthManagerK o instance (GObject o, IsDescendantOf AuthManager o) => AuthManagerK o toAuthManager :: AuthManagerK o => o -> IO AuthManager toAuthManager = unsafeCastTo AuthManager -- method AuthManager::use_auth -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthManager", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "auth", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "AuthManager", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "auth", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_auth_manager_use_auth" soup_auth_manager_use_auth :: Ptr AuthManager -> -- _obj : TInterface "Soup" "AuthManager" Ptr URI -> -- uri : TInterface "Soup" "URI" Ptr Auth -> -- auth : TInterface "Soup" "Auth" IO () authManagerUseAuth :: (MonadIO m, AuthManagerK a, AuthK b) => a -> -- _obj URI -> -- uri b -> -- auth m () authManagerUseAuth _obj uri auth = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let uri' = unsafeManagedPtrGetPtr uri let auth' = unsafeManagedPtrCastPtr auth soup_auth_manager_use_auth _obj' uri' auth' touchManagedPtr _obj touchManagedPtr uri touchManagedPtr auth return () -- signal AuthManager::authenticate type AuthManagerAuthenticateCallback = Message -> Auth -> Bool -> IO () noAuthManagerAuthenticateCallback :: Maybe AuthManagerAuthenticateCallback noAuthManagerAuthenticateCallback = Nothing type AuthManagerAuthenticateCallbackC = Ptr () -> -- object Ptr Message -> Ptr Auth -> CInt -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkAuthManagerAuthenticateCallback :: AuthManagerAuthenticateCallbackC -> IO (FunPtr AuthManagerAuthenticateCallbackC) authManagerAuthenticateClosure :: AuthManagerAuthenticateCallback -> IO Closure authManagerAuthenticateClosure cb = newCClosure =<< mkAuthManagerAuthenticateCallback wrapped where wrapped = authManagerAuthenticateCallbackWrapper cb authManagerAuthenticateCallbackWrapper :: AuthManagerAuthenticateCallback -> Ptr () -> Ptr Message -> Ptr Auth -> CInt -> Ptr () -> IO () authManagerAuthenticateCallbackWrapper _cb _ msg auth retrying _ = do msg' <- (newObject Message) msg auth' <- (newObject Auth) auth let retrying' = (/= 0) retrying _cb msg' auth' retrying' onAuthManagerAuthenticate :: (GObject a, MonadIO m) => a -> AuthManagerAuthenticateCallback -> m SignalHandlerId onAuthManagerAuthenticate obj cb = liftIO $ connectAuthManagerAuthenticate obj cb SignalConnectBefore afterAuthManagerAuthenticate :: (GObject a, MonadIO m) => a -> AuthManagerAuthenticateCallback -> m SignalHandlerId afterAuthManagerAuthenticate obj cb = connectAuthManagerAuthenticate obj cb SignalConnectAfter connectAuthManagerAuthenticate :: (GObject a, MonadIO m) => a -> AuthManagerAuthenticateCallback -> SignalConnectMode -> m SignalHandlerId connectAuthManagerAuthenticate obj cb after = liftIO $ do cb' <- mkAuthManagerAuthenticateCallback (authManagerAuthenticateCallbackWrapper cb) connectSignalFunPtr obj "authenticate" cb' after -- object AuthNTLM newtype AuthNTLM = AuthNTLM (ForeignPtr AuthNTLM) noAuthNTLM :: Maybe AuthNTLM noAuthNTLM = Nothing foreign import ccall "soup_auth_ntlm_get_type" c_soup_auth_ntlm_get_type :: IO GType type instance ParentTypes AuthNTLM = '[Auth, GObject.Object] instance GObject AuthNTLM where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_auth_ntlm_get_type class GObject o => AuthNTLMK o instance (GObject o, IsDescendantOf AuthNTLM o) => AuthNTLMK o toAuthNTLM :: AuthNTLMK o => o -> IO AuthNTLM toAuthNTLM = unsafeCastTo AuthNTLM -- struct Buffer newtype Buffer = Buffer (ForeignPtr Buffer) noBuffer :: Maybe Buffer noBuffer = Nothing foreign import ccall "soup_buffer_get_type" c_soup_buffer_get_type :: IO GType instance BoxedObject Buffer where boxedType _ = c_soup_buffer_get_type bufferReadData :: Buffer -> IO (Ptr ()) bufferReadData s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 0) :: IO (Ptr ()) return val bufferReadLength :: Buffer -> IO Word64 bufferReadLength s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 8) :: IO Word64 return val -- method Buffer::new -- method type : Constructor -- Args : [Arg {argName = "data", argType = TCArray False (-1) 1 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- hInArgs : [Arg {argName = "data", argType = TCArray False (-1) 1 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- returnType : TInterface "Soup" "Buffer" -- throws : False -- Skip return : False foreign import ccall "soup_buffer_new_take" soup_buffer_new_take :: Ptr Word8 -> -- data : TCArray False (-1) 1 (TBasicType TUInt8) Word64 -> -- length : TBasicType TUInt64 IO (Ptr Buffer) bufferNew :: (MonadIO m) => ByteString -> -- data m Buffer bufferNew data_ = liftIO $ do let length_ = fromIntegral $ B.length data_ data_' <- packByteString data_ result <- soup_buffer_new_take data_' length_ checkUnexpectedReturnNULL "soup_buffer_new_take" result result' <- (wrapBoxed Buffer) result return result' -- method Buffer::new_with_owner -- method type : Constructor -- Args : [Arg {argName = "data", argType = TCArray False (-1) 1 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "owner", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "owner_dnotify", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- hInArgs : [Arg {argName = "data", argType = TCArray False (-1) 1 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "owner", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "owner_dnotify", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Buffer" -- throws : False -- Skip return : False foreign import ccall "soup_buffer_new_with_owner" soup_buffer_new_with_owner :: Ptr Word8 -> -- data : TCArray False (-1) 1 (TBasicType TUInt8) Word64 -> -- length : TBasicType TUInt64 Ptr () -> -- owner : TBasicType TVoid FunPtr GLib.DestroyNotifyC -> -- owner_dnotify : TInterface "GLib" "DestroyNotify" IO (Ptr Buffer) bufferNewWithOwner :: (MonadIO m) => ByteString -> -- data Ptr () -> -- owner Maybe (GLib.DestroyNotify) -> -- owner_dnotify m Buffer bufferNewWithOwner data_ owner owner_dnotify = liftIO $ do let length_ = fromIntegral $ B.length data_ data_' <- packByteString data_ ptrowner_dnotify <- callocMem :: IO (Ptr (FunPtr GLib.DestroyNotifyC)) maybeOwner_dnotify <- case owner_dnotify of Nothing -> return (castPtrToFunPtr nullPtr) Just jOwner_dnotify -> do jOwner_dnotify' <- GLib.mkDestroyNotify (GLib.destroyNotifyWrapper (Just ptrowner_dnotify) jOwner_dnotify) poke ptrowner_dnotify jOwner_dnotify' return jOwner_dnotify' result <- soup_buffer_new_with_owner data_' length_ owner maybeOwner_dnotify checkUnexpectedReturnNULL "soup_buffer_new_with_owner" result result' <- (wrapBoxed Buffer) result freeMem data_' return result' -- method Buffer::copy -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Buffer" -- throws : False -- Skip return : False foreign import ccall "soup_buffer_copy" soup_buffer_copy :: Ptr Buffer -> -- _obj : TInterface "Soup" "Buffer" IO (Ptr Buffer) bufferCopy :: (MonadIO m) => Buffer -> -- _obj m Buffer bufferCopy _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_buffer_copy _obj' checkUnexpectedReturnNULL "soup_buffer_copy" result result' <- (wrapBoxed Buffer) result touchManagedPtr _obj return result' -- method Buffer::free -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_buffer_free" soup_buffer_free :: Ptr Buffer -> -- _obj : TInterface "Soup" "Buffer" IO () bufferFree :: (MonadIO m) => Buffer -> -- _obj m () bufferFree _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj soup_buffer_free _obj' touchManagedPtr _obj return () -- method Buffer::get_as_bytes -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "GLib" "Bytes" -- throws : False -- Skip return : False foreign import ccall "soup_buffer_get_as_bytes" soup_buffer_get_as_bytes :: Ptr Buffer -> -- _obj : TInterface "Soup" "Buffer" IO (Ptr GLib.Bytes) bufferGetAsBytes :: (MonadIO m) => Buffer -> -- _obj m GLib.Bytes bufferGetAsBytes _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_buffer_get_as_bytes _obj' checkUnexpectedReturnNULL "soup_buffer_get_as_bytes" result result' <- (wrapBoxed GLib.Bytes) result touchManagedPtr _obj return result' -- method Buffer::get_data -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- Lengths : [Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_buffer_get_data" soup_buffer_get_data :: Ptr Buffer -> -- _obj : TInterface "Soup" "Buffer" Ptr (Ptr Word8) -> -- data : TCArray False (-1) 2 (TBasicType TUInt8) Ptr Word64 -> -- length : TBasicType TUInt64 IO () bufferGetData :: (MonadIO m) => Buffer -> -- _obj m (ByteString) bufferGetData _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj data_ <- allocMem :: IO (Ptr (Ptr Word8)) length_ <- allocMem :: IO (Ptr Word64) soup_buffer_get_data _obj' data_ length_ length_' <- peek length_ data_' <- peek data_ data_'' <- (unpackByteStringWithLength length_') data_' touchManagedPtr _obj freeMem data_ freeMem length_ return data_'' -- method Buffer::get_owner -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_buffer_get_owner" soup_buffer_get_owner :: Ptr Buffer -> -- _obj : TInterface "Soup" "Buffer" IO () bufferGetOwner :: (MonadIO m) => Buffer -> -- _obj m () bufferGetOwner _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj soup_buffer_get_owner _obj' touchManagedPtr _obj return () -- method Buffer::new_subbuffer -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "offset", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "offset", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Buffer" -- throws : False -- Skip return : False foreign import ccall "soup_buffer_new_subbuffer" soup_buffer_new_subbuffer :: Ptr Buffer -> -- _obj : TInterface "Soup" "Buffer" Word64 -> -- offset : TBasicType TUInt64 Word64 -> -- length : TBasicType TUInt64 IO (Ptr Buffer) bufferNewSubbuffer :: (MonadIO m) => Buffer -> -- _obj Word64 -> -- offset Word64 -> -- length m Buffer bufferNewSubbuffer _obj offset length_ = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_buffer_new_subbuffer _obj' offset length_ checkUnexpectedReturnNULL "soup_buffer_new_subbuffer" result result' <- (wrapBoxed Buffer) result touchManagedPtr _obj return result' -- object Cache newtype Cache = Cache (ForeignPtr Cache) noCache :: Maybe Cache noCache = Nothing foreign import ccall "soup_cache_get_type" c_soup_cache_get_type :: IO GType type instance ParentTypes Cache = '[GObject.Object, SessionFeature] instance GObject Cache where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_cache_get_type class GObject o => CacheK o instance (GObject o, IsDescendantOf Cache o) => CacheK o toCache :: CacheK o => o -> IO Cache toCache = unsafeCastTo Cache -- method Cache::new -- method type : Constructor -- Args : [Arg {argName = "cache_dir", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cache_type", argType = TInterface "Soup" "CacheType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "cache_dir", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cache_type", argType = TInterface "Soup" "CacheType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Cache" -- throws : False -- Skip return : False foreign import ccall "soup_cache_new" soup_cache_new :: CString -> -- cache_dir : TBasicType TUTF8 CUInt -> -- cache_type : TInterface "Soup" "CacheType" IO (Ptr Cache) cacheNew :: (MonadIO m) => T.Text -> -- cache_dir CacheType -> -- cache_type m Cache cacheNew cache_dir cache_type = liftIO $ do cache_dir' <- textToCString cache_dir let cache_type' = (fromIntegral . fromEnum) cache_type result <- soup_cache_new cache_dir' cache_type' checkUnexpectedReturnNULL "soup_cache_new" result result' <- (wrapObject Cache) result freeMem cache_dir' return result' -- method Cache::clear -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cache", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cache", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_cache_clear" soup_cache_clear :: Ptr Cache -> -- _obj : TInterface "Soup" "Cache" IO () cacheClear :: (MonadIO m, CacheK a) => a -> -- _obj m () cacheClear _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_cache_clear _obj' touchManagedPtr _obj return () -- method Cache::dump -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cache", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cache", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_cache_dump" soup_cache_dump :: Ptr Cache -> -- _obj : TInterface "Soup" "Cache" IO () cacheDump :: (MonadIO m, CacheK a) => a -> -- _obj m () cacheDump _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_cache_dump _obj' touchManagedPtr _obj return () -- method Cache::flush -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cache", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cache", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_cache_flush" soup_cache_flush :: Ptr Cache -> -- _obj : TInterface "Soup" "Cache" IO () cacheFlush :: (MonadIO m, CacheK a) => a -> -- _obj m () cacheFlush _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_cache_flush _obj' touchManagedPtr _obj return () -- method Cache::get_max_size -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cache", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cache", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_cache_get_max_size" soup_cache_get_max_size :: Ptr Cache -> -- _obj : TInterface "Soup" "Cache" IO Word32 cacheGetMaxSize :: (MonadIO m, CacheK a) => a -> -- _obj m Word32 cacheGetMaxSize _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_cache_get_max_size _obj' touchManagedPtr _obj return result -- method Cache::load -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cache", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cache", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_cache_load" soup_cache_load :: Ptr Cache -> -- _obj : TInterface "Soup" "Cache" IO () cacheLoad :: (MonadIO m, CacheK a) => a -> -- _obj m () cacheLoad _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_cache_load _obj' touchManagedPtr _obj return () -- method Cache::set_max_size -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cache", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "max_size", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cache", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "max_size", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_cache_set_max_size" soup_cache_set_max_size :: Ptr Cache -> -- _obj : TInterface "Soup" "Cache" Word32 -> -- max_size : TBasicType TUInt32 IO () cacheSetMaxSize :: (MonadIO m, CacheK a) => a -> -- _obj Word32 -> -- max_size m () cacheSetMaxSize _obj max_size = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_cache_set_max_size _obj' max_size touchManagedPtr _obj return () -- Enum CacheResponse data CacheResponse = CacheResponseFresh | CacheResponseNeedsValidation | CacheResponseStale | AnotherCacheResponse Int deriving (Show, Eq) instance Enum CacheResponse where fromEnum CacheResponseFresh = 0 fromEnum CacheResponseNeedsValidation = 1 fromEnum CacheResponseStale = 2 fromEnum (AnotherCacheResponse k) = k toEnum 0 = CacheResponseFresh toEnum 1 = CacheResponseNeedsValidation toEnum 2 = CacheResponseStale toEnum k = AnotherCacheResponse k foreign import ccall "soup_cache_response_get_type" c_soup_cache_response_get_type :: IO GType instance BoxedEnum CacheResponse where boxedEnumType _ = c_soup_cache_response_get_type -- Enum CacheType data CacheType = CacheTypeSingleUser | CacheTypeShared | AnotherCacheType Int deriving (Show, Eq) instance Enum CacheType where fromEnum CacheTypeSingleUser = 0 fromEnum CacheTypeShared = 1 fromEnum (AnotherCacheType k) = k toEnum 0 = CacheTypeSingleUser toEnum 1 = CacheTypeShared toEnum k = AnotherCacheType k foreign import ccall "soup_cache_type_get_type" c_soup_cache_type_get_type :: IO GType instance BoxedEnum CacheType where boxedEnumType _ = c_soup_cache_type_get_type -- Flags Cacheability data Cacheability = CacheabilityCacheable | CacheabilityUncacheable | CacheabilityInvalidates | CacheabilityValidates | AnotherCacheability Int deriving (Show, Eq) instance Enum Cacheability where fromEnum CacheabilityCacheable = 1 fromEnum CacheabilityUncacheable = 2 fromEnum CacheabilityInvalidates = 4 fromEnum CacheabilityValidates = 8 fromEnum (AnotherCacheability k) = k toEnum 1 = CacheabilityCacheable toEnum 2 = CacheabilityUncacheable toEnum 4 = CacheabilityInvalidates toEnum 8 = CacheabilityValidates toEnum k = AnotherCacheability k foreign import ccall "soup_cacheability_get_type" c_soup_cacheability_get_type :: IO GType instance BoxedEnum Cacheability where boxedEnumType _ = c_soup_cacheability_get_type instance IsGFlag Cacheability -- callback ChunkAllocator chunkAllocatorClosure :: ChunkAllocator -> IO Closure chunkAllocatorClosure cb = newCClosure =<< mkChunkAllocator wrapped where wrapped = chunkAllocatorWrapper Nothing cb type ChunkAllocatorC = Ptr Message -> Word64 -> Ptr () -> IO (Ptr Buffer) foreign import ccall "wrapper" mkChunkAllocator :: ChunkAllocatorC -> IO (FunPtr ChunkAllocatorC) type ChunkAllocator = Message -> Word64 -> IO Buffer noChunkAllocator :: Maybe ChunkAllocator noChunkAllocator = Nothing chunkAllocatorWrapper :: Maybe (Ptr (FunPtr (ChunkAllocatorC))) -> ChunkAllocator -> Ptr Message -> Word64 -> Ptr () -> IO (Ptr Buffer) chunkAllocatorWrapper funptrptr _cb msg max_len _ = do msg' <- (newObject Message) msg result <- _cb msg' max_len maybeReleaseFunPtr funptrptr result' <- copyBoxed result return result' -- struct ClientContext newtype ClientContext = ClientContext (ForeignPtr ClientContext) noClientContext :: Maybe ClientContext noClientContext = Nothing foreign import ccall "soup_client_context_get_type" c_soup_client_context_get_type :: IO GType instance BoxedObject ClientContext where boxedType _ = c_soup_client_context_get_type -- method ClientContext::get_address -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Address" -- throws : False -- Skip return : False foreign import ccall "soup_client_context_get_address" soup_client_context_get_address :: Ptr ClientContext -> -- _obj : TInterface "Soup" "ClientContext" IO (Ptr Address) {-# DEPRECATED clientContextGetAddress ["Use soup_client_context_get_remote_address(), which returns","a #GSocketAddress."]#-} clientContextGetAddress :: (MonadIO m) => ClientContext -> -- _obj m Address clientContextGetAddress _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_client_context_get_address _obj' checkUnexpectedReturnNULL "soup_client_context_get_address" result result' <- (newObject Address) result touchManagedPtr _obj return result' -- method ClientContext::get_auth_domain -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "AuthDomain" -- throws : False -- Skip return : False foreign import ccall "soup_client_context_get_auth_domain" soup_client_context_get_auth_domain :: Ptr ClientContext -> -- _obj : TInterface "Soup" "ClientContext" IO (Ptr AuthDomain) clientContextGetAuthDomain :: (MonadIO m) => ClientContext -> -- _obj m AuthDomain clientContextGetAuthDomain _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_client_context_get_auth_domain _obj' checkUnexpectedReturnNULL "soup_client_context_get_auth_domain" result result' <- (newObject AuthDomain) result touchManagedPtr _obj return result' -- method ClientContext::get_auth_user -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_client_context_get_auth_user" soup_client_context_get_auth_user :: Ptr ClientContext -> -- _obj : TInterface "Soup" "ClientContext" IO CString clientContextGetAuthUser :: (MonadIO m) => ClientContext -> -- _obj m T.Text clientContextGetAuthUser _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_client_context_get_auth_user _obj' checkUnexpectedReturnNULL "soup_client_context_get_auth_user" result result' <- cstringToText result touchManagedPtr _obj return result' -- method ClientContext::get_gsocket -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Gio" "Socket" -- throws : False -- Skip return : False foreign import ccall "soup_client_context_get_gsocket" soup_client_context_get_gsocket :: Ptr ClientContext -> -- _obj : TInterface "Soup" "ClientContext" IO (Ptr Gio.Socket) clientContextGetGsocket :: (MonadIO m) => ClientContext -> -- _obj m Gio.Socket clientContextGetGsocket _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_client_context_get_gsocket _obj' checkUnexpectedReturnNULL "soup_client_context_get_gsocket" result result' <- (newObject Gio.Socket) result touchManagedPtr _obj return result' -- method ClientContext::get_host -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_client_context_get_host" soup_client_context_get_host :: Ptr ClientContext -> -- _obj : TInterface "Soup" "ClientContext" IO CString clientContextGetHost :: (MonadIO m) => ClientContext -> -- _obj m T.Text clientContextGetHost _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_client_context_get_host _obj' checkUnexpectedReturnNULL "soup_client_context_get_host" result result' <- cstringToText result touchManagedPtr _obj return result' -- method ClientContext::get_local_address -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Gio" "SocketAddress" -- throws : False -- Skip return : False foreign import ccall "soup_client_context_get_local_address" soup_client_context_get_local_address :: Ptr ClientContext -> -- _obj : TInterface "Soup" "ClientContext" IO (Ptr Gio.SocketAddress) clientContextGetLocalAddress :: (MonadIO m) => ClientContext -> -- _obj m Gio.SocketAddress clientContextGetLocalAddress _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_client_context_get_local_address _obj' checkUnexpectedReturnNULL "soup_client_context_get_local_address" result result' <- (newObject Gio.SocketAddress) result touchManagedPtr _obj return result' -- method ClientContext::get_remote_address -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Gio" "SocketAddress" -- throws : False -- Skip return : False foreign import ccall "soup_client_context_get_remote_address" soup_client_context_get_remote_address :: Ptr ClientContext -> -- _obj : TInterface "Soup" "ClientContext" IO (Ptr Gio.SocketAddress) clientContextGetRemoteAddress :: (MonadIO m) => ClientContext -> -- _obj m Gio.SocketAddress clientContextGetRemoteAddress _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_client_context_get_remote_address _obj' checkUnexpectedReturnNULL "soup_client_context_get_remote_address" result result' <- (newObject Gio.SocketAddress) result touchManagedPtr _obj return result' -- method ClientContext::get_socket -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Socket" -- throws : False -- Skip return : False foreign import ccall "soup_client_context_get_socket" soup_client_context_get_socket :: Ptr ClientContext -> -- _obj : TInterface "Soup" "ClientContext" IO (Ptr Socket) {-# DEPRECATED clientContextGetSocket ["use soup_client_context_get_gsocket(), which returns","a #GSocket."]#-} clientContextGetSocket :: (MonadIO m) => ClientContext -> -- _obj m Socket clientContextGetSocket _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_client_context_get_socket _obj' checkUnexpectedReturnNULL "soup_client_context_get_socket" result result' <- (newObject Socket) result touchManagedPtr _obj return result' -- method ClientContext::steal_connection -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "ClientContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Gio" "IOStream" -- throws : False -- Skip return : False foreign import ccall "soup_client_context_steal_connection" soup_client_context_steal_connection :: Ptr ClientContext -> -- _obj : TInterface "Soup" "ClientContext" IO (Ptr Gio.IOStream) clientContextStealConnection :: (MonadIO m) => ClientContext -> -- _obj m Gio.IOStream clientContextStealConnection _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_client_context_steal_connection _obj' checkUnexpectedReturnNULL "soup_client_context_steal_connection" result result' <- (wrapObject Gio.IOStream) result touchManagedPtr _obj return result' -- struct Connection newtype Connection = Connection (ForeignPtr Connection) noConnection :: Maybe Connection noConnection = Nothing -- Enum ConnectionState data ConnectionState = ConnectionStateNew | ConnectionStateConnecting | ConnectionStateIdle | ConnectionStateInUse | ConnectionStateRemoteDisconnected | ConnectionStateDisconnected | AnotherConnectionState Int deriving (Show, Eq) instance Enum ConnectionState where fromEnum ConnectionStateNew = 0 fromEnum ConnectionStateConnecting = 1 fromEnum ConnectionStateIdle = 2 fromEnum ConnectionStateInUse = 3 fromEnum ConnectionStateRemoteDisconnected = 4 fromEnum ConnectionStateDisconnected = 5 fromEnum (AnotherConnectionState k) = k toEnum 0 = ConnectionStateNew toEnum 1 = ConnectionStateConnecting toEnum 2 = ConnectionStateIdle toEnum 3 = ConnectionStateInUse toEnum 4 = ConnectionStateRemoteDisconnected toEnum 5 = ConnectionStateDisconnected toEnum k = AnotherConnectionState k foreign import ccall "soup_connection_state_get_type" c_soup_connection_state_get_type :: IO GType instance BoxedEnum ConnectionState where boxedEnumType _ = c_soup_connection_state_get_type -- object ContentDecoder newtype ContentDecoder = ContentDecoder (ForeignPtr ContentDecoder) noContentDecoder :: Maybe ContentDecoder noContentDecoder = Nothing foreign import ccall "soup_content_decoder_get_type" c_soup_content_decoder_get_type :: IO GType type instance ParentTypes ContentDecoder = '[GObject.Object, SessionFeature] instance GObject ContentDecoder where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_content_decoder_get_type class GObject o => ContentDecoderK o instance (GObject o, IsDescendantOf ContentDecoder o) => ContentDecoderK o toContentDecoder :: ContentDecoderK o => o -> IO ContentDecoder toContentDecoder = unsafeCastTo ContentDecoder -- object ContentSniffer newtype ContentSniffer = ContentSniffer (ForeignPtr ContentSniffer) noContentSniffer :: Maybe ContentSniffer noContentSniffer = Nothing foreign import ccall "soup_content_sniffer_get_type" c_soup_content_sniffer_get_type :: IO GType type instance ParentTypes ContentSniffer = '[GObject.Object, SessionFeature] instance GObject ContentSniffer where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_content_sniffer_get_type class GObject o => ContentSnifferK o instance (GObject o, IsDescendantOf ContentSniffer o) => ContentSnifferK o toContentSniffer :: ContentSnifferK o => o -> IO ContentSniffer toContentSniffer = unsafeCastTo ContentSniffer -- method ContentSniffer::new -- method type : Constructor -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TInterface "Soup" "ContentSniffer" -- throws : False -- Skip return : False foreign import ccall "soup_content_sniffer_new" soup_content_sniffer_new :: IO (Ptr ContentSniffer) contentSnifferNew :: (MonadIO m) => m ContentSniffer contentSnifferNew = liftIO $ do result <- soup_content_sniffer_new checkUnexpectedReturnNULL "soup_content_sniffer_new" result result' <- (wrapObject ContentSniffer) result return result' -- method ContentSniffer::get_buffer_size -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "ContentSniffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "ContentSniffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUInt64 -- throws : False -- Skip return : False foreign import ccall "soup_content_sniffer_get_buffer_size" soup_content_sniffer_get_buffer_size :: Ptr ContentSniffer -> -- _obj : TInterface "Soup" "ContentSniffer" IO Word64 contentSnifferGetBufferSize :: (MonadIO m, ContentSnifferK a) => a -> -- _obj m Word64 contentSnifferGetBufferSize _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_content_sniffer_get_buffer_size _obj' touchManagedPtr _obj return result -- method ContentSniffer::sniff -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "ContentSniffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer", argType = TInterface "Soup" "Buffer", 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" "ContentSniffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_content_sniffer_sniff" soup_content_sniffer_sniff :: Ptr ContentSniffer -> -- _obj : TInterface "Soup" "ContentSniffer" Ptr Message -> -- msg : TInterface "Soup" "Message" Ptr Buffer -> -- buffer : TInterface "Soup" "Buffer" Ptr (Ptr (GHashTable CString CString)) -> -- params : TGHash (TBasicType TUTF8) (TBasicType TUTF8) IO CString contentSnifferSniff :: (MonadIO m, ContentSnifferK a, MessageK b) => a -> -- _obj b -> -- msg Buffer -> -- buffer m (T.Text,(Map.Map T.Text T.Text)) contentSnifferSniff _obj msg buffer = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg let buffer' = unsafeManagedPtrGetPtr buffer params <- allocMem :: IO (Ptr (Ptr (GHashTable CString CString))) result <- soup_content_sniffer_sniff _obj' msg' buffer' params checkUnexpectedReturnNULL "soup_content_sniffer_sniff" result result' <- cstringToText result freeMem 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 touchManagedPtr msg touchManagedPtr buffer freeMem params return (result', params''''''') -- struct Cookie newtype Cookie = Cookie (ForeignPtr Cookie) noCookie :: Maybe Cookie noCookie = Nothing foreign import ccall "soup_cookie_get_type" c_soup_cookie_get_type :: IO GType instance BoxedObject Cookie where boxedType _ = c_soup_cookie_get_type cookieReadName :: Cookie -> IO T.Text cookieReadName s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 0) :: IO CString val' <- cstringToText val return val' cookieReadValue :: Cookie -> IO T.Text cookieReadValue s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 8) :: IO CString val' <- cstringToText val return val' cookieReadDomain :: Cookie -> IO T.Text cookieReadDomain s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 16) :: IO CString val' <- cstringToText val return val' cookieReadPath :: Cookie -> IO T.Text cookieReadPath s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 24) :: IO CString val' <- cstringToText val return val' cookieReadExpires :: Cookie -> IO Date cookieReadExpires s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 32) :: IO (Ptr Date) val' <- (newBoxed Date) val return val' cookieReadSecure :: Cookie -> IO Bool cookieReadSecure s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 40) :: IO CInt let val' = (/= 0) val return val' cookieReadHttpOnly :: Cookie -> IO Bool cookieReadHttpOnly s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 44) :: IO CInt let val' = (/= 0) val return val' -- method Cookie::new -- method type : Constructor -- Args : [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},Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "max_age", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [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},Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "max_age", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Cookie" -- throws : False -- Skip return : False foreign import ccall "soup_cookie_new" soup_cookie_new :: CString -> -- name : TBasicType TUTF8 CString -> -- value : TBasicType TUTF8 CString -> -- domain : TBasicType TUTF8 CString -> -- path : TBasicType TUTF8 Int32 -> -- max_age : TBasicType TInt32 IO (Ptr Cookie) cookieNew :: (MonadIO m) => T.Text -> -- name T.Text -> -- value T.Text -> -- domain T.Text -> -- path Int32 -> -- max_age m Cookie cookieNew name value domain path max_age = liftIO $ do name' <- textToCString name value' <- textToCString value domain' <- textToCString domain path' <- textToCString path result <- soup_cookie_new name' value' domain' path' max_age checkUnexpectedReturnNULL "soup_cookie_new" result result' <- (wrapBoxed Cookie) result freeMem name' freeMem value' freeMem domain' freeMem path' return result' -- method Cookie::applies_to_uri -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_cookie_applies_to_uri" soup_cookie_applies_to_uri :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" Ptr URI -> -- uri : TInterface "Soup" "URI" IO CInt cookieAppliesToUri :: (MonadIO m) => Cookie -> -- _obj URI -> -- uri m Bool cookieAppliesToUri _obj uri = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj let uri' = unsafeManagedPtrGetPtr uri result <- soup_cookie_applies_to_uri _obj' uri' let result' = (/= 0) result touchManagedPtr _obj touchManagedPtr uri return result' -- method Cookie::copy -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Cookie" -- throws : False -- Skip return : False foreign import ccall "soup_cookie_copy" soup_cookie_copy :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" IO (Ptr Cookie) cookieCopy :: (MonadIO m) => Cookie -> -- _obj m Cookie cookieCopy _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_cookie_copy _obj' checkUnexpectedReturnNULL "soup_cookie_copy" result result' <- (wrapBoxed Cookie) result touchManagedPtr _obj return result' -- method Cookie::domain_matches -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "host", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "host", 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_cookie_domain_matches" soup_cookie_domain_matches :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" CString -> -- host : TBasicType TUTF8 IO CInt cookieDomainMatches :: (MonadIO m) => Cookie -> -- _obj T.Text -> -- host m Bool cookieDomainMatches _obj host = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj host' <- textToCString host result <- soup_cookie_domain_matches _obj' host' let result' = (/= 0) result touchManagedPtr _obj freeMem host' return result' -- method Cookie::equal -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cookie2", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cookie2", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_cookie_equal" soup_cookie_equal :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" Ptr Cookie -> -- cookie2 : TInterface "Soup" "Cookie" IO CInt cookieEqual :: (MonadIO m) => Cookie -> -- _obj Cookie -> -- cookie2 m Bool cookieEqual _obj cookie2 = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj let cookie2' = unsafeManagedPtrGetPtr cookie2 result <- soup_cookie_equal _obj' cookie2' let result' = (/= 0) result touchManagedPtr _obj touchManagedPtr cookie2 return result' -- method Cookie::free -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_cookie_free" soup_cookie_free :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" IO () cookieFree :: (MonadIO m) => Cookie -> -- _obj m () cookieFree _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj soup_cookie_free _obj' touchManagedPtr _obj return () -- method Cookie::get_domain -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_cookie_get_domain" soup_cookie_get_domain :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" IO CString cookieGetDomain :: (MonadIO m) => Cookie -> -- _obj m T.Text cookieGetDomain _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_cookie_get_domain _obj' checkUnexpectedReturnNULL "soup_cookie_get_domain" result result' <- cstringToText result touchManagedPtr _obj return result' -- method Cookie::get_expires -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Date" -- throws : False -- Skip return : False foreign import ccall "soup_cookie_get_expires" soup_cookie_get_expires :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" IO (Ptr Date) cookieGetExpires :: (MonadIO m) => Cookie -> -- _obj m Date cookieGetExpires _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_cookie_get_expires _obj' checkUnexpectedReturnNULL "soup_cookie_get_expires" result result' <- (newBoxed Date) result touchManagedPtr _obj return result' -- method Cookie::get_http_only -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_cookie_get_http_only" soup_cookie_get_http_only :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" IO CInt cookieGetHttpOnly :: (MonadIO m) => Cookie -> -- _obj m Bool cookieGetHttpOnly _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_cookie_get_http_only _obj' let result' = (/= 0) result touchManagedPtr _obj return result' -- method Cookie::get_name -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_cookie_get_name" soup_cookie_get_name :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" IO CString cookieGetName :: (MonadIO m) => Cookie -> -- _obj m T.Text cookieGetName _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_cookie_get_name _obj' checkUnexpectedReturnNULL "soup_cookie_get_name" result result' <- cstringToText result touchManagedPtr _obj return result' -- method Cookie::get_path -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_cookie_get_path" soup_cookie_get_path :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" IO CString cookieGetPath :: (MonadIO m) => Cookie -> -- _obj m T.Text cookieGetPath _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_cookie_get_path _obj' checkUnexpectedReturnNULL "soup_cookie_get_path" result result' <- cstringToText result touchManagedPtr _obj return result' -- method Cookie::get_secure -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_cookie_get_secure" soup_cookie_get_secure :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" IO CInt cookieGetSecure :: (MonadIO m) => Cookie -> -- _obj m Bool cookieGetSecure _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_cookie_get_secure _obj' let result' = (/= 0) result touchManagedPtr _obj return result' -- method Cookie::get_value -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_cookie_get_value" soup_cookie_get_value :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" IO CString cookieGetValue :: (MonadIO m) => Cookie -> -- _obj m T.Text cookieGetValue _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_cookie_get_value _obj' checkUnexpectedReturnNULL "soup_cookie_get_value" result result' <- cstringToText result touchManagedPtr _obj return result' -- method Cookie::set_domain -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "domain", 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_cookie_set_domain" soup_cookie_set_domain :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" CString -> -- domain : TBasicType TUTF8 IO () cookieSetDomain :: (MonadIO m) => Cookie -> -- _obj T.Text -> -- domain m () cookieSetDomain _obj domain = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj domain' <- textToCString domain soup_cookie_set_domain _obj' domain' touchManagedPtr _obj freeMem domain' return () -- method Cookie::set_expires -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "expires", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "expires", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_cookie_set_expires" soup_cookie_set_expires :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" Ptr Date -> -- expires : TInterface "Soup" "Date" IO () cookieSetExpires :: (MonadIO m) => Cookie -> -- _obj Date -> -- expires m () cookieSetExpires _obj expires = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj let expires' = unsafeManagedPtrGetPtr expires soup_cookie_set_expires _obj' expires' touchManagedPtr _obj touchManagedPtr expires return () -- method Cookie::set_http_only -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "http_only", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "http_only", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_cookie_set_http_only" soup_cookie_set_http_only :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" CInt -> -- http_only : TBasicType TBoolean IO () cookieSetHttpOnly :: (MonadIO m) => Cookie -> -- _obj Bool -> -- http_only m () cookieSetHttpOnly _obj http_only = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj let http_only' = (fromIntegral . fromEnum) http_only soup_cookie_set_http_only _obj' http_only' touchManagedPtr _obj return () -- method Cookie::set_max_age -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "max_age", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "max_age", 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_cookie_set_max_age" soup_cookie_set_max_age :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" Int32 -> -- max_age : TBasicType TInt32 IO () cookieSetMaxAge :: (MonadIO m) => Cookie -> -- _obj Int32 -> -- max_age m () cookieSetMaxAge _obj max_age = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj soup_cookie_set_max_age _obj' max_age touchManagedPtr _obj return () -- method Cookie::set_name -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", 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" "Cookie", 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_cookie_set_name" soup_cookie_set_name :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" CString -> -- name : TBasicType TUTF8 IO () cookieSetName :: (MonadIO m) => Cookie -> -- _obj T.Text -> -- name m () cookieSetName _obj name = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj name' <- textToCString name soup_cookie_set_name _obj' name' touchManagedPtr _obj freeMem name' return () -- method Cookie::set_path -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", 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_cookie_set_path" soup_cookie_set_path :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" CString -> -- path : TBasicType TUTF8 IO () cookieSetPath :: (MonadIO m) => Cookie -> -- _obj T.Text -> -- path m () cookieSetPath _obj path = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj path' <- textToCString path soup_cookie_set_path _obj' path' touchManagedPtr _obj freeMem path' return () -- method Cookie::set_secure -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "secure", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "secure", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_cookie_set_secure" soup_cookie_set_secure :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" CInt -> -- secure : TBasicType TBoolean IO () cookieSetSecure :: (MonadIO m) => Cookie -> -- _obj Bool -> -- secure m () cookieSetSecure _obj secure = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj let secure' = (fromIntegral . fromEnum) secure soup_cookie_set_secure _obj' secure' touchManagedPtr _obj return () -- method Cookie::set_value -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", 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" "Cookie", 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_cookie_set_value" soup_cookie_set_value :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" CString -> -- value : TBasicType TUTF8 IO () cookieSetValue :: (MonadIO m) => Cookie -> -- _obj T.Text -> -- value m () cookieSetValue _obj value = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj value' <- textToCString value soup_cookie_set_value _obj' value' touchManagedPtr _obj freeMem value' return () -- method Cookie::to_cookie_header -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_cookie_to_cookie_header" soup_cookie_to_cookie_header :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" IO CString cookieToCookieHeader :: (MonadIO m) => Cookie -> -- _obj m T.Text cookieToCookieHeader _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_cookie_to_cookie_header _obj' checkUnexpectedReturnNULL "soup_cookie_to_cookie_header" result result' <- cstringToText result freeMem result touchManagedPtr _obj return result' -- method Cookie::to_set_cookie_header -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_cookie_to_set_cookie_header" soup_cookie_to_set_cookie_header :: Ptr Cookie -> -- _obj : TInterface "Soup" "Cookie" IO CString cookieToSetCookieHeader :: (MonadIO m) => Cookie -> -- _obj m T.Text cookieToSetCookieHeader _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_cookie_to_set_cookie_header _obj' checkUnexpectedReturnNULL "soup_cookie_to_set_cookie_header" result result' <- cstringToText result freeMem result touchManagedPtr _obj return result' -- object CookieJar newtype CookieJar = CookieJar (ForeignPtr CookieJar) noCookieJar :: Maybe CookieJar noCookieJar = Nothing foreign import ccall "soup_cookie_jar_get_type" c_soup_cookie_jar_get_type :: IO GType type instance ParentTypes CookieJar = '[GObject.Object, SessionFeature] instance GObject CookieJar where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_cookie_jar_get_type class GObject o => CookieJarK o instance (GObject o, IsDescendantOf CookieJar o) => CookieJarK o toCookieJar :: CookieJarK o => o -> IO CookieJar toCookieJar = unsafeCastTo CookieJar -- method CookieJar::new -- method type : Constructor -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TInterface "Soup" "CookieJar" -- throws : False -- Skip return : False foreign import ccall "soup_cookie_jar_new" soup_cookie_jar_new :: IO (Ptr CookieJar) cookieJarNew :: (MonadIO m) => m CookieJar cookieJarNew = liftIO $ do result <- soup_cookie_jar_new checkUnexpectedReturnNULL "soup_cookie_jar_new" result result' <- (wrapObject CookieJar) result return result' -- method CookieJar::add_cookie -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cookie", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cookie", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_cookie_jar_add_cookie" soup_cookie_jar_add_cookie :: Ptr CookieJar -> -- _obj : TInterface "Soup" "CookieJar" Ptr Cookie -> -- cookie : TInterface "Soup" "Cookie" IO () cookieJarAddCookie :: (MonadIO m, CookieJarK a) => a -> -- _obj Cookie -> -- cookie m () cookieJarAddCookie _obj cookie = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj cookie' <- copyBoxed cookie soup_cookie_jar_add_cookie _obj' cookie' touchManagedPtr _obj touchManagedPtr cookie return () -- method CookieJar::add_cookie_with_first_party -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "first_party", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cookie", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "first_party", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cookie", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_cookie_jar_add_cookie_with_first_party" soup_cookie_jar_add_cookie_with_first_party :: Ptr CookieJar -> -- _obj : TInterface "Soup" "CookieJar" Ptr URI -> -- first_party : TInterface "Soup" "URI" Ptr Cookie -> -- cookie : TInterface "Soup" "Cookie" IO () cookieJarAddCookieWithFirstParty :: (MonadIO m, CookieJarK a) => a -> -- _obj URI -> -- first_party Cookie -> -- cookie m () cookieJarAddCookieWithFirstParty _obj first_party cookie = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let first_party' = unsafeManagedPtrGetPtr first_party cookie' <- copyBoxed cookie soup_cookie_jar_add_cookie_with_first_party _obj' first_party' cookie' touchManagedPtr _obj touchManagedPtr first_party touchManagedPtr cookie return () -- method CookieJar::all_cookies -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TGSList (TInterface "Soup" "Cookie") -- throws : False -- Skip return : False foreign import ccall "soup_cookie_jar_all_cookies" soup_cookie_jar_all_cookies :: Ptr CookieJar -> -- _obj : TInterface "Soup" "CookieJar" IO (Ptr (GSList (Ptr Cookie))) cookieJarAllCookies :: (MonadIO m, CookieJarK a) => a -> -- _obj m [Cookie] cookieJarAllCookies _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_cookie_jar_all_cookies _obj' checkUnexpectedReturnNULL "soup_cookie_jar_all_cookies" result result' <- unpackGSList result result'' <- mapM (wrapBoxed Cookie) result' g_slist_free result touchManagedPtr _obj return result'' -- method CookieJar::delete_cookie -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cookie", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cookie", argType = TInterface "Soup" "Cookie", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_cookie_jar_delete_cookie" soup_cookie_jar_delete_cookie :: Ptr CookieJar -> -- _obj : TInterface "Soup" "CookieJar" Ptr Cookie -> -- cookie : TInterface "Soup" "Cookie" IO () cookieJarDeleteCookie :: (MonadIO m, CookieJarK a) => a -> -- _obj Cookie -> -- cookie m () cookieJarDeleteCookie _obj cookie = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let cookie' = unsafeManagedPtrGetPtr cookie soup_cookie_jar_delete_cookie _obj' cookie' touchManagedPtr _obj touchManagedPtr cookie return () -- method CookieJar::get_accept_policy -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "CookieJarAcceptPolicy" -- throws : False -- Skip return : False foreign import ccall "soup_cookie_jar_get_accept_policy" soup_cookie_jar_get_accept_policy :: Ptr CookieJar -> -- _obj : TInterface "Soup" "CookieJar" IO CUInt cookieJarGetAcceptPolicy :: (MonadIO m, CookieJarK a) => a -> -- _obj m CookieJarAcceptPolicy cookieJarGetAcceptPolicy _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_cookie_jar_get_accept_policy _obj' let result' = (toEnum . fromIntegral) result touchManagedPtr _obj return result' -- method CookieJar::get_cookie_list -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "for_http", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "for_http", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TGSList (TInterface "Soup" "Cookie") -- throws : False -- Skip return : False foreign import ccall "soup_cookie_jar_get_cookie_list" soup_cookie_jar_get_cookie_list :: Ptr CookieJar -> -- _obj : TInterface "Soup" "CookieJar" Ptr URI -> -- uri : TInterface "Soup" "URI" CInt -> -- for_http : TBasicType TBoolean IO (Ptr (GSList (Ptr Cookie))) cookieJarGetCookieList :: (MonadIO m, CookieJarK a) => a -> -- _obj URI -> -- uri Bool -> -- for_http m [Cookie] cookieJarGetCookieList _obj uri for_http = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let uri' = unsafeManagedPtrGetPtr uri let for_http' = (fromIntegral . fromEnum) for_http result <- soup_cookie_jar_get_cookie_list _obj' uri' for_http' checkUnexpectedReturnNULL "soup_cookie_jar_get_cookie_list" result result' <- unpackGSList result result'' <- mapM (wrapBoxed Cookie) result' g_slist_free result touchManagedPtr _obj touchManagedPtr uri return result'' -- method CookieJar::get_cookies -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "for_http", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "for_http", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_cookie_jar_get_cookies" soup_cookie_jar_get_cookies :: Ptr CookieJar -> -- _obj : TInterface "Soup" "CookieJar" Ptr URI -> -- uri : TInterface "Soup" "URI" CInt -> -- for_http : TBasicType TBoolean IO CString cookieJarGetCookies :: (MonadIO m, CookieJarK a) => a -> -- _obj URI -> -- uri Bool -> -- for_http m T.Text cookieJarGetCookies _obj uri for_http = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let uri' = unsafeManagedPtrGetPtr uri let for_http' = (fromIntegral . fromEnum) for_http result <- soup_cookie_jar_get_cookies _obj' uri' for_http' checkUnexpectedReturnNULL "soup_cookie_jar_get_cookies" result result' <- cstringToText result freeMem result touchManagedPtr _obj touchManagedPtr uri return result' -- method CookieJar::is_persistent -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_cookie_jar_is_persistent" soup_cookie_jar_is_persistent :: Ptr CookieJar -> -- _obj : TInterface "Soup" "CookieJar" IO CInt cookieJarIsPersistent :: (MonadIO m, CookieJarK a) => a -> -- _obj m Bool cookieJarIsPersistent _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_cookie_jar_is_persistent _obj' let result' = (/= 0) result touchManagedPtr _obj return result' -- method CookieJar::save -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_cookie_jar_save" soup_cookie_jar_save :: Ptr CookieJar -> -- _obj : TInterface "Soup" "CookieJar" IO () {-# DEPRECATED cookieJarSave ["This is a no-op."]#-} cookieJarSave :: (MonadIO m, CookieJarK a) => a -> -- _obj m () cookieJarSave _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_cookie_jar_save _obj' touchManagedPtr _obj return () -- method CookieJar::set_accept_policy -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "policy", argType = TInterface "Soup" "CookieJarAcceptPolicy", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "policy", argType = TInterface "Soup" "CookieJarAcceptPolicy", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_cookie_jar_set_accept_policy" soup_cookie_jar_set_accept_policy :: Ptr CookieJar -> -- _obj : TInterface "Soup" "CookieJar" CUInt -> -- policy : TInterface "Soup" "CookieJarAcceptPolicy" IO () cookieJarSetAcceptPolicy :: (MonadIO m, CookieJarK a) => a -> -- _obj CookieJarAcceptPolicy -> -- policy m () cookieJarSetAcceptPolicy _obj policy = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let policy' = (fromIntegral . fromEnum) policy soup_cookie_jar_set_accept_policy _obj' policy' touchManagedPtr _obj return () -- method CookieJar::set_cookie -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cookie", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cookie", 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_cookie_jar_set_cookie" soup_cookie_jar_set_cookie :: Ptr CookieJar -> -- _obj : TInterface "Soup" "CookieJar" Ptr URI -> -- uri : TInterface "Soup" "URI" CString -> -- cookie : TBasicType TUTF8 IO () cookieJarSetCookie :: (MonadIO m, CookieJarK a) => a -> -- _obj URI -> -- uri T.Text -> -- cookie m () cookieJarSetCookie _obj uri cookie = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let uri' = unsafeManagedPtrGetPtr uri cookie' <- textToCString cookie soup_cookie_jar_set_cookie _obj' uri' cookie' touchManagedPtr _obj touchManagedPtr uri freeMem cookie' return () -- method CookieJar::set_cookie_with_first_party -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "first_party", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cookie", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "CookieJar", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "first_party", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cookie", 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_cookie_jar_set_cookie_with_first_party" soup_cookie_jar_set_cookie_with_first_party :: Ptr CookieJar -> -- _obj : TInterface "Soup" "CookieJar" Ptr URI -> -- uri : TInterface "Soup" "URI" Ptr URI -> -- first_party : TInterface "Soup" "URI" CString -> -- cookie : TBasicType TUTF8 IO () cookieJarSetCookieWithFirstParty :: (MonadIO m, CookieJarK a) => a -> -- _obj URI -> -- uri URI -> -- first_party T.Text -> -- cookie m () cookieJarSetCookieWithFirstParty _obj uri first_party cookie = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let uri' = unsafeManagedPtrGetPtr uri let first_party' = unsafeManagedPtrGetPtr first_party cookie' <- textToCString cookie soup_cookie_jar_set_cookie_with_first_party _obj' uri' first_party' cookie' touchManagedPtr _obj touchManagedPtr uri touchManagedPtr first_party freeMem cookie' return () -- signal CookieJar::changed type CookieJarChangedCallback = Cookie -> Cookie -> IO () noCookieJarChangedCallback :: Maybe CookieJarChangedCallback noCookieJarChangedCallback = Nothing type CookieJarChangedCallbackC = Ptr () -> -- object Ptr Cookie -> Ptr Cookie -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkCookieJarChangedCallback :: CookieJarChangedCallbackC -> IO (FunPtr CookieJarChangedCallbackC) cookieJarChangedClosure :: CookieJarChangedCallback -> IO Closure cookieJarChangedClosure cb = newCClosure =<< mkCookieJarChangedCallback wrapped where wrapped = cookieJarChangedCallbackWrapper cb cookieJarChangedCallbackWrapper :: CookieJarChangedCallback -> Ptr () -> Ptr Cookie -> Ptr Cookie -> Ptr () -> IO () cookieJarChangedCallbackWrapper _cb _ old_cookie new_cookie _ = do old_cookie' <- (newBoxed Cookie) old_cookie new_cookie' <- (newBoxed Cookie) new_cookie _cb old_cookie' new_cookie' onCookieJarChanged :: (GObject a, MonadIO m) => a -> CookieJarChangedCallback -> m SignalHandlerId onCookieJarChanged obj cb = liftIO $ connectCookieJarChanged obj cb SignalConnectBefore afterCookieJarChanged :: (GObject a, MonadIO m) => a -> CookieJarChangedCallback -> m SignalHandlerId afterCookieJarChanged obj cb = connectCookieJarChanged obj cb SignalConnectAfter connectCookieJarChanged :: (GObject a, MonadIO m) => a -> CookieJarChangedCallback -> SignalConnectMode -> m SignalHandlerId connectCookieJarChanged obj cb after = liftIO $ do cb' <- mkCookieJarChangedCallback (cookieJarChangedCallbackWrapper cb) connectSignalFunPtr obj "changed" cb' after -- Enum CookieJarAcceptPolicy data CookieJarAcceptPolicy = CookieJarAcceptPolicyAlways | CookieJarAcceptPolicyNever | CookieJarAcceptPolicyNoThirdParty | AnotherCookieJarAcceptPolicy Int deriving (Show, Eq) instance Enum CookieJarAcceptPolicy where fromEnum CookieJarAcceptPolicyAlways = 0 fromEnum CookieJarAcceptPolicyNever = 1 fromEnum CookieJarAcceptPolicyNoThirdParty = 2 fromEnum (AnotherCookieJarAcceptPolicy k) = k toEnum 0 = CookieJarAcceptPolicyAlways toEnum 1 = CookieJarAcceptPolicyNever toEnum 2 = CookieJarAcceptPolicyNoThirdParty toEnum k = AnotherCookieJarAcceptPolicy k foreign import ccall "soup_cookie_jar_accept_policy_get_type" c_soup_cookie_jar_accept_policy_get_type :: IO GType instance BoxedEnum CookieJarAcceptPolicy where boxedEnumType _ = c_soup_cookie_jar_accept_policy_get_type -- object CookieJarDB newtype CookieJarDB = CookieJarDB (ForeignPtr CookieJarDB) noCookieJarDB :: Maybe CookieJarDB noCookieJarDB = Nothing foreign import ccall "soup_cookie_jar_db_get_type" c_soup_cookie_jar_db_get_type :: IO GType type instance ParentTypes CookieJarDB = '[CookieJar, GObject.Object, SessionFeature] instance GObject CookieJarDB where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_cookie_jar_db_get_type class GObject o => CookieJarDBK o instance (GObject o, IsDescendantOf CookieJarDB o) => CookieJarDBK o toCookieJarDB :: CookieJarDBK o => o -> IO CookieJarDB toCookieJarDB = unsafeCastTo CookieJarDB -- method CookieJarDB::new -- method type : Constructor -- Args : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "read_only", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "read_only", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "CookieJarDB" -- throws : False -- Skip return : False foreign import ccall "soup_cookie_jar_db_new" soup_cookie_jar_db_new :: CString -> -- filename : TBasicType TUTF8 CInt -> -- read_only : TBasicType TBoolean IO (Ptr CookieJarDB) cookieJarDBNew :: (MonadIO m) => T.Text -> -- filename Bool -> -- read_only m CookieJarDB cookieJarDBNew filename read_only = liftIO $ do filename' <- textToCString filename let read_only' = (fromIntegral . fromEnum) read_only result <- soup_cookie_jar_db_new filename' read_only' checkUnexpectedReturnNULL "soup_cookie_jar_db_new" result result' <- (wrapObject CookieJarDB) result freeMem filename' return result' -- object CookieJarText newtype CookieJarText = CookieJarText (ForeignPtr CookieJarText) noCookieJarText :: Maybe CookieJarText noCookieJarText = Nothing foreign import ccall "soup_cookie_jar_text_get_type" c_soup_cookie_jar_text_get_type :: IO GType type instance ParentTypes CookieJarText = '[CookieJar, GObject.Object, SessionFeature] instance GObject CookieJarText where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_cookie_jar_text_get_type class GObject o => CookieJarTextK o instance (GObject o, IsDescendantOf CookieJarText o) => CookieJarTextK o toCookieJarText :: CookieJarTextK o => o -> IO CookieJarText toCookieJarText = unsafeCastTo CookieJarText -- method CookieJarText::new -- method type : Constructor -- Args : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "read_only", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "read_only", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "CookieJarText" -- throws : False -- Skip return : False foreign import ccall "soup_cookie_jar_text_new" soup_cookie_jar_text_new :: CString -> -- filename : TBasicType TUTF8 CInt -> -- read_only : TBasicType TBoolean IO (Ptr CookieJarText) cookieJarTextNew :: (MonadIO m) => T.Text -> -- filename Bool -> -- read_only m CookieJarText cookieJarTextNew filename read_only = liftIO $ do filename' <- textToCString filename let read_only' = (fromIntegral . fromEnum) read_only result <- soup_cookie_jar_text_new filename' read_only' checkUnexpectedReturnNULL "soup_cookie_jar_text_new" result result' <- (wrapObject CookieJarText) result freeMem filename' return result' -- struct Date newtype Date = Date (ForeignPtr Date) noDate :: Maybe Date noDate = Nothing foreign import ccall "soup_date_get_type" c_soup_date_get_type :: IO GType instance BoxedObject Date where boxedType _ = c_soup_date_get_type dateReadYear :: Date -> IO Int32 dateReadYear s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 0) :: IO Int32 return val dateReadMonth :: Date -> IO Int32 dateReadMonth s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 4) :: IO Int32 return val dateReadDay :: Date -> IO Int32 dateReadDay s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 8) :: IO Int32 return val dateReadHour :: Date -> IO Int32 dateReadHour s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 12) :: IO Int32 return val dateReadMinute :: Date -> IO Int32 dateReadMinute s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 16) :: IO Int32 return val dateReadSecond :: Date -> IO Int32 dateReadSecond s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 20) :: IO Int32 return val dateReadUtc :: Date -> IO Bool dateReadUtc s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 24) :: IO CInt let val' = (/= 0) val return val' dateReadOffset :: Date -> IO Int32 dateReadOffset s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 28) :: IO Int32 return val -- method Date::new -- method type : Constructor -- Args : [Arg {argName = "year", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "month", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "day", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hour", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "minute", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "second", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "year", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "month", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "day", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hour", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "minute", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "second", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Date" -- throws : False -- Skip return : False foreign import ccall "soup_date_new" soup_date_new :: Int32 -> -- year : TBasicType TInt32 Int32 -> -- month : TBasicType TInt32 Int32 -> -- day : TBasicType TInt32 Int32 -> -- hour : TBasicType TInt32 Int32 -> -- minute : TBasicType TInt32 Int32 -> -- second : TBasicType TInt32 IO (Ptr Date) dateNew :: (MonadIO m) => Int32 -> -- year Int32 -> -- month Int32 -> -- day Int32 -> -- hour Int32 -> -- minute Int32 -> -- second m Date dateNew year month day hour minute second = liftIO $ do result <- soup_date_new year month day hour minute second checkUnexpectedReturnNULL "soup_date_new" result result' <- (wrapBoxed Date) result return result' -- method Date::new_from_now -- method type : Constructor -- Args : [Arg {argName = "offset_seconds", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "offset_seconds", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Date" -- throws : False -- Skip return : False foreign import ccall "soup_date_new_from_now" soup_date_new_from_now :: Int32 -> -- offset_seconds : TBasicType TInt32 IO (Ptr Date) dateNewFromNow :: (MonadIO m) => Int32 -> -- offset_seconds m Date dateNewFromNow offset_seconds = liftIO $ do result <- soup_date_new_from_now offset_seconds checkUnexpectedReturnNULL "soup_date_new_from_now" result result' <- (wrapBoxed Date) result return result' -- method Date::new_from_string -- method type : Constructor -- Args : [Arg {argName = "date_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "date_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Date" -- throws : False -- Skip return : False foreign import ccall "soup_date_new_from_string" soup_date_new_from_string :: CString -> -- date_string : TBasicType TUTF8 IO (Ptr Date) dateNewFromString :: (MonadIO m) => T.Text -> -- date_string m Date dateNewFromString date_string = liftIO $ do date_string' <- textToCString date_string result <- soup_date_new_from_string date_string' checkUnexpectedReturnNULL "soup_date_new_from_string" result result' <- (wrapBoxed Date) result freeMem date_string' return result' -- method Date::new_from_time_t -- method type : Constructor -- Args : [Arg {argName = "when", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "when", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Date" -- throws : False -- Skip return : False foreign import ccall "soup_date_new_from_time_t" soup_date_new_from_time_t :: Int64 -> -- when : TBasicType TInt64 IO (Ptr Date) dateNewFromTimeT :: (MonadIO m) => Int64 -> -- when m Date dateNewFromTimeT when_ = liftIO $ do result <- soup_date_new_from_time_t when_ checkUnexpectedReturnNULL "soup_date_new_from_time_t" result result' <- (wrapBoxed Date) result return result' -- method Date::copy -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Date" -- throws : False -- Skip return : False foreign import ccall "soup_date_copy" soup_date_copy :: Ptr Date -> -- _obj : TInterface "Soup" "Date" IO (Ptr Date) dateCopy :: (MonadIO m) => Date -> -- _obj m Date dateCopy _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_date_copy _obj' checkUnexpectedReturnNULL "soup_date_copy" result result' <- (wrapBoxed Date) result touchManagedPtr _obj return result' -- method Date::free -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_date_free" soup_date_free :: Ptr Date -> -- _obj : TInterface "Soup" "Date" IO () dateFree :: (MonadIO m) => Date -> -- _obj m () dateFree _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj soup_date_free _obj' touchManagedPtr _obj return () -- method Date::get_day -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TInt32 -- throws : False -- Skip return : False foreign import ccall "soup_date_get_day" soup_date_get_day :: Ptr Date -> -- _obj : TInterface "Soup" "Date" IO Int32 dateGetDay :: (MonadIO m) => Date -> -- _obj m Int32 dateGetDay _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_date_get_day _obj' touchManagedPtr _obj return result -- method Date::get_hour -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TInt32 -- throws : False -- Skip return : False foreign import ccall "soup_date_get_hour" soup_date_get_hour :: Ptr Date -> -- _obj : TInterface "Soup" "Date" IO Int32 dateGetHour :: (MonadIO m) => Date -> -- _obj m Int32 dateGetHour _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_date_get_hour _obj' touchManagedPtr _obj return result -- method Date::get_minute -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TInt32 -- throws : False -- Skip return : False foreign import ccall "soup_date_get_minute" soup_date_get_minute :: Ptr Date -> -- _obj : TInterface "Soup" "Date" IO Int32 dateGetMinute :: (MonadIO m) => Date -> -- _obj m Int32 dateGetMinute _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_date_get_minute _obj' touchManagedPtr _obj return result -- method Date::get_month -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TInt32 -- throws : False -- Skip return : False foreign import ccall "soup_date_get_month" soup_date_get_month :: Ptr Date -> -- _obj : TInterface "Soup" "Date" IO Int32 dateGetMonth :: (MonadIO m) => Date -> -- _obj m Int32 dateGetMonth _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_date_get_month _obj' touchManagedPtr _obj return result -- method Date::get_offset -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TInt32 -- throws : False -- Skip return : False foreign import ccall "soup_date_get_offset" soup_date_get_offset :: Ptr Date -> -- _obj : TInterface "Soup" "Date" IO Int32 dateGetOffset :: (MonadIO m) => Date -> -- _obj m Int32 dateGetOffset _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_date_get_offset _obj' touchManagedPtr _obj return result -- method Date::get_second -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TInt32 -- throws : False -- Skip return : False foreign import ccall "soup_date_get_second" soup_date_get_second :: Ptr Date -> -- _obj : TInterface "Soup" "Date" IO Int32 dateGetSecond :: (MonadIO m) => Date -> -- _obj m Int32 dateGetSecond _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_date_get_second _obj' touchManagedPtr _obj return result -- method Date::get_utc -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TInt32 -- throws : False -- Skip return : False foreign import ccall "soup_date_get_utc" soup_date_get_utc :: Ptr Date -> -- _obj : TInterface "Soup" "Date" IO Int32 dateGetUtc :: (MonadIO m) => Date -> -- _obj m Int32 dateGetUtc _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_date_get_utc _obj' touchManagedPtr _obj return result -- method Date::get_year -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TInt32 -- throws : False -- Skip return : False foreign import ccall "soup_date_get_year" soup_date_get_year :: Ptr Date -> -- _obj : TInterface "Soup" "Date" IO Int32 dateGetYear :: (MonadIO m) => Date -> -- _obj m Int32 dateGetYear _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_date_get_year _obj' touchManagedPtr _obj return result -- method Date::is_past -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_date_is_past" soup_date_is_past :: Ptr Date -> -- _obj : TInterface "Soup" "Date" IO CInt dateIsPast :: (MonadIO m) => Date -> -- _obj m Bool dateIsPast _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_date_is_past _obj' let result' = (/= 0) result touchManagedPtr _obj return result' -- method Date::to_string -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "format", argType = TInterface "Soup" "DateFormat", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "format", argType = TInterface "Soup" "DateFormat", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_date_to_string" soup_date_to_string :: Ptr Date -> -- _obj : TInterface "Soup" "Date" CUInt -> -- format : TInterface "Soup" "DateFormat" IO CString dateToString :: (MonadIO m) => Date -> -- _obj DateFormat -> -- format m T.Text dateToString _obj format = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj let format' = (fromIntegral . fromEnum) format result <- soup_date_to_string _obj' format' checkUnexpectedReturnNULL "soup_date_to_string" result result' <- cstringToText result freeMem result touchManagedPtr _obj return result' -- method Date::to_time_t -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TInt64 -- throws : False -- Skip return : False foreign import ccall "soup_date_to_time_t" soup_date_to_time_t :: Ptr Date -> -- _obj : TInterface "Soup" "Date" IO Int64 dateToTimeT :: (MonadIO m) => Date -> -- _obj m Int64 dateToTimeT _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_date_to_time_t _obj' touchManagedPtr _obj return result -- method Date::to_timeval -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "time", argType = TInterface "GLib" "TimeVal", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_date_to_timeval" soup_date_to_timeval :: Ptr Date -> -- _obj : TInterface "Soup" "Date" Ptr GLib.TimeVal -> -- time : TInterface "GLib" "TimeVal" IO () dateToTimeval :: (MonadIO m) => Date -> -- _obj m (GLib.TimeVal) dateToTimeval _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj time <- callocBytes 16 :: IO (Ptr GLib.TimeVal) soup_date_to_timeval _obj' time time' <- (wrapPtr GLib.TimeVal) time touchManagedPtr _obj return time' -- Enum DateFormat data DateFormat = DateFormatHttp | DateFormatCookie | DateFormatRfc2822 | DateFormatIso8601Compact | DateFormatIso8601Full | DateFormatIso8601 | DateFormatIso8601Xmlrpc | AnotherDateFormat Int deriving (Show, Eq) instance Enum DateFormat where fromEnum DateFormatHttp = 1 fromEnum DateFormatCookie = 2 fromEnum DateFormatRfc2822 = 3 fromEnum DateFormatIso8601Compact = 4 fromEnum DateFormatIso8601Full = 5 fromEnum DateFormatIso8601 = 5 fromEnum DateFormatIso8601Xmlrpc = 6 fromEnum (AnotherDateFormat k) = k toEnum 1 = DateFormatHttp toEnum 2 = DateFormatCookie toEnum 3 = DateFormatRfc2822 toEnum 4 = DateFormatIso8601Compact toEnum 5 = DateFormatIso8601Full toEnum 6 = DateFormatIso8601Xmlrpc toEnum k = AnotherDateFormat k foreign import ccall "soup_date_format_get_type" c_soup_date_format_get_type :: IO GType instance BoxedEnum DateFormat where boxedEnumType _ = c_soup_date_format_get_type -- Enum Encoding data Encoding = EncodingUnrecognized | EncodingNone | EncodingContentLength | EncodingEof | EncodingChunked | EncodingByteranges | AnotherEncoding Int deriving (Show, Eq) instance Enum Encoding where fromEnum EncodingUnrecognized = 0 fromEnum EncodingNone = 1 fromEnum EncodingContentLength = 2 fromEnum EncodingEof = 3 fromEnum EncodingChunked = 4 fromEnum EncodingByteranges = 5 fromEnum (AnotherEncoding k) = k toEnum 0 = EncodingUnrecognized toEnum 1 = EncodingNone toEnum 2 = EncodingContentLength toEnum 3 = EncodingEof toEnum 4 = EncodingChunked toEnum 5 = EncodingByteranges toEnum k = AnotherEncoding k foreign import ccall "soup_encoding_get_type" c_soup_encoding_get_type :: IO GType instance BoxedEnum Encoding where boxedEnumType _ = c_soup_encoding_get_type -- Flags Expectation data Expectation = ExpectationUnrecognized | ExpectationContinue | AnotherExpectation Int deriving (Show, Eq) instance Enum Expectation where fromEnum ExpectationUnrecognized = 1 fromEnum ExpectationContinue = 2 fromEnum (AnotherExpectation k) = k toEnum 1 = ExpectationUnrecognized toEnum 2 = ExpectationContinue toEnum k = AnotherExpectation k foreign import ccall "soup_expectation_get_type" c_soup_expectation_get_type :: IO GType instance BoxedEnum Expectation where boxedEnumType _ = c_soup_expectation_get_type instance IsGFlag Expectation -- Enum HTTPVersion data HTTPVersion = HTTPVersionHttp10 | HTTPVersionHttp11 | AnotherHTTPVersion Int deriving (Show, Eq) instance Enum HTTPVersion where fromEnum HTTPVersionHttp10 = 0 fromEnum HTTPVersionHttp11 = 1 fromEnum (AnotherHTTPVersion k) = k toEnum 0 = HTTPVersionHttp10 toEnum 1 = HTTPVersionHttp11 toEnum k = AnotherHTTPVersion k foreign import ccall "soup_http_version_get_type" c_soup_http_version_get_type :: IO GType instance BoxedEnum HTTPVersion where boxedEnumType _ = c_soup_http_version_get_type -- Enum KnownStatusCode data KnownStatusCode = KnownStatusCodeNone | KnownStatusCodeCancelled | KnownStatusCodeCantResolve | KnownStatusCodeCantResolveProxy | KnownStatusCodeCantConnect | KnownStatusCodeCantConnectProxy | KnownStatusCodeSslFailed | KnownStatusCodeIoError | KnownStatusCodeMalformed | KnownStatusCodeTryAgain | KnownStatusCodeTooManyRedirects | KnownStatusCodeTlsFailed | KnownStatusCodeContinue | KnownStatusCodeSwitchingProtocols | KnownStatusCodeProcessing | KnownStatusCodeOk | KnownStatusCodeCreated | KnownStatusCodeAccepted | KnownStatusCodeNonAuthoritative | KnownStatusCodeNoContent | KnownStatusCodeResetContent | KnownStatusCodePartialContent | KnownStatusCodeMultiStatus | KnownStatusCodeMultipleChoices | KnownStatusCodeMovedPermanently | KnownStatusCodeFound | KnownStatusCodeMovedTemporarily | KnownStatusCodeSeeOther | KnownStatusCodeNotModified | KnownStatusCodeUseProxy | KnownStatusCodeNotAppearingInThisProtocol | KnownStatusCodeTemporaryRedirect | KnownStatusCodeBadRequest | KnownStatusCodeUnauthorized | KnownStatusCodePaymentRequired | KnownStatusCodeForbidden | KnownStatusCodeNotFound | KnownStatusCodeMethodNotAllowed | KnownStatusCodeNotAcceptable | KnownStatusCodeProxyAuthenticationRequired | KnownStatusCodeProxyUnauthorized | KnownStatusCodeRequestTimeout | KnownStatusCodeConflict | KnownStatusCodeGone | KnownStatusCodeLengthRequired | KnownStatusCodePreconditionFailed | KnownStatusCodeRequestEntityTooLarge | KnownStatusCodeRequestUriTooLong | KnownStatusCodeUnsupportedMediaType | KnownStatusCodeRequestedRangeNotSatisfiable | KnownStatusCodeInvalidRange | KnownStatusCodeExpectationFailed | KnownStatusCodeUnprocessableEntity | KnownStatusCodeLocked | KnownStatusCodeFailedDependency | KnownStatusCodeInternalServerError | KnownStatusCodeNotImplemented | KnownStatusCodeBadGateway | KnownStatusCodeServiceUnavailable | KnownStatusCodeGatewayTimeout | KnownStatusCodeHttpVersionNotSupported | KnownStatusCodeInsufficientStorage | KnownStatusCodeNotExtended | AnotherKnownStatusCode Int deriving (Show, Eq) instance Enum KnownStatusCode where fromEnum KnownStatusCodeNone = 0 fromEnum KnownStatusCodeCancelled = 1 fromEnum KnownStatusCodeCantResolve = 2 fromEnum KnownStatusCodeCantResolveProxy = 3 fromEnum KnownStatusCodeCantConnect = 4 fromEnum KnownStatusCodeCantConnectProxy = 5 fromEnum KnownStatusCodeSslFailed = 6 fromEnum KnownStatusCodeIoError = 7 fromEnum KnownStatusCodeMalformed = 8 fromEnum KnownStatusCodeTryAgain = 9 fromEnum KnownStatusCodeTooManyRedirects = 10 fromEnum KnownStatusCodeTlsFailed = 11 fromEnum KnownStatusCodeContinue = 100 fromEnum KnownStatusCodeSwitchingProtocols = 101 fromEnum KnownStatusCodeProcessing = 102 fromEnum KnownStatusCodeOk = 200 fromEnum KnownStatusCodeCreated = 201 fromEnum KnownStatusCodeAccepted = 202 fromEnum KnownStatusCodeNonAuthoritative = 203 fromEnum KnownStatusCodeNoContent = 204 fromEnum KnownStatusCodeResetContent = 205 fromEnum KnownStatusCodePartialContent = 206 fromEnum KnownStatusCodeMultiStatus = 207 fromEnum KnownStatusCodeMultipleChoices = 300 fromEnum KnownStatusCodeMovedPermanently = 301 fromEnum KnownStatusCodeFound = 302 fromEnum KnownStatusCodeMovedTemporarily = 302 fromEnum KnownStatusCodeSeeOther = 303 fromEnum KnownStatusCodeNotModified = 304 fromEnum KnownStatusCodeUseProxy = 305 fromEnum KnownStatusCodeNotAppearingInThisProtocol = 306 fromEnum KnownStatusCodeTemporaryRedirect = 307 fromEnum KnownStatusCodeBadRequest = 400 fromEnum KnownStatusCodeUnauthorized = 401 fromEnum KnownStatusCodePaymentRequired = 402 fromEnum KnownStatusCodeForbidden = 403 fromEnum KnownStatusCodeNotFound = 404 fromEnum KnownStatusCodeMethodNotAllowed = 405 fromEnum KnownStatusCodeNotAcceptable = 406 fromEnum KnownStatusCodeProxyAuthenticationRequired = 407 fromEnum KnownStatusCodeProxyUnauthorized = 407 fromEnum KnownStatusCodeRequestTimeout = 408 fromEnum KnownStatusCodeConflict = 409 fromEnum KnownStatusCodeGone = 410 fromEnum KnownStatusCodeLengthRequired = 411 fromEnum KnownStatusCodePreconditionFailed = 412 fromEnum KnownStatusCodeRequestEntityTooLarge = 413 fromEnum KnownStatusCodeRequestUriTooLong = 414 fromEnum KnownStatusCodeUnsupportedMediaType = 415 fromEnum KnownStatusCodeRequestedRangeNotSatisfiable = 416 fromEnum KnownStatusCodeInvalidRange = 416 fromEnum KnownStatusCodeExpectationFailed = 417 fromEnum KnownStatusCodeUnprocessableEntity = 422 fromEnum KnownStatusCodeLocked = 423 fromEnum KnownStatusCodeFailedDependency = 424 fromEnum KnownStatusCodeInternalServerError = 500 fromEnum KnownStatusCodeNotImplemented = 501 fromEnum KnownStatusCodeBadGateway = 502 fromEnum KnownStatusCodeServiceUnavailable = 503 fromEnum KnownStatusCodeGatewayTimeout = 504 fromEnum KnownStatusCodeHttpVersionNotSupported = 505 fromEnum KnownStatusCodeInsufficientStorage = 507 fromEnum KnownStatusCodeNotExtended = 510 fromEnum (AnotherKnownStatusCode k) = k toEnum 0 = KnownStatusCodeNone toEnum 1 = KnownStatusCodeCancelled toEnum 2 = KnownStatusCodeCantResolve toEnum 3 = KnownStatusCodeCantResolveProxy toEnum 4 = KnownStatusCodeCantConnect toEnum 5 = KnownStatusCodeCantConnectProxy toEnum 6 = KnownStatusCodeSslFailed toEnum 7 = KnownStatusCodeIoError toEnum 8 = KnownStatusCodeMalformed toEnum 9 = KnownStatusCodeTryAgain toEnum 10 = KnownStatusCodeTooManyRedirects toEnum 11 = KnownStatusCodeTlsFailed toEnum 100 = KnownStatusCodeContinue toEnum 101 = KnownStatusCodeSwitchingProtocols toEnum 102 = KnownStatusCodeProcessing toEnum 200 = KnownStatusCodeOk toEnum 201 = KnownStatusCodeCreated toEnum 202 = KnownStatusCodeAccepted toEnum 203 = KnownStatusCodeNonAuthoritative toEnum 204 = KnownStatusCodeNoContent toEnum 205 = KnownStatusCodeResetContent toEnum 206 = KnownStatusCodePartialContent toEnum 207 = KnownStatusCodeMultiStatus toEnum 300 = KnownStatusCodeMultipleChoices toEnum 301 = KnownStatusCodeMovedPermanently toEnum 302 = KnownStatusCodeFound toEnum 303 = KnownStatusCodeSeeOther toEnum 304 = KnownStatusCodeNotModified toEnum 305 = KnownStatusCodeUseProxy toEnum 306 = KnownStatusCodeNotAppearingInThisProtocol toEnum 307 = KnownStatusCodeTemporaryRedirect toEnum 400 = KnownStatusCodeBadRequest toEnum 401 = KnownStatusCodeUnauthorized toEnum 402 = KnownStatusCodePaymentRequired toEnum 403 = KnownStatusCodeForbidden toEnum 404 = KnownStatusCodeNotFound toEnum 405 = KnownStatusCodeMethodNotAllowed toEnum 406 = KnownStatusCodeNotAcceptable toEnum 407 = KnownStatusCodeProxyAuthenticationRequired toEnum 408 = KnownStatusCodeRequestTimeout toEnum 409 = KnownStatusCodeConflict toEnum 410 = KnownStatusCodeGone toEnum 411 = KnownStatusCodeLengthRequired toEnum 412 = KnownStatusCodePreconditionFailed toEnum 413 = KnownStatusCodeRequestEntityTooLarge toEnum 414 = KnownStatusCodeRequestUriTooLong toEnum 415 = KnownStatusCodeUnsupportedMediaType toEnum 416 = KnownStatusCodeRequestedRangeNotSatisfiable toEnum 417 = KnownStatusCodeExpectationFailed toEnum 422 = KnownStatusCodeUnprocessableEntity toEnum 423 = KnownStatusCodeLocked toEnum 424 = KnownStatusCodeFailedDependency toEnum 500 = KnownStatusCodeInternalServerError toEnum 501 = KnownStatusCodeNotImplemented toEnum 502 = KnownStatusCodeBadGateway toEnum 503 = KnownStatusCodeServiceUnavailable toEnum 504 = KnownStatusCodeGatewayTimeout toEnum 505 = KnownStatusCodeHttpVersionNotSupported toEnum 507 = KnownStatusCodeInsufficientStorage toEnum 510 = KnownStatusCodeNotExtended toEnum k = AnotherKnownStatusCode k foreign import ccall "soup_known_status_code_get_type" c_soup_known_status_code_get_type :: IO GType instance BoxedEnum KnownStatusCode where boxedEnumType _ = c_soup_known_status_code_get_type -- object Logger newtype Logger = Logger (ForeignPtr Logger) noLogger :: Maybe Logger noLogger = Nothing foreign import ccall "soup_logger_get_type" c_soup_logger_get_type :: IO GType type instance ParentTypes Logger = '[GObject.Object, SessionFeature] instance GObject Logger where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_logger_get_type class GObject o => LoggerK o instance (GObject o, IsDescendantOf Logger o) => LoggerK o toLogger :: LoggerK o => o -> IO Logger toLogger = unsafeCastTo Logger -- method Logger::new -- method type : Constructor -- Args : [Arg {argName = "level", argType = TInterface "Soup" "LoggerLogLevel", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "max_body_size", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "level", argType = TInterface "Soup" "LoggerLogLevel", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "max_body_size", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Logger" -- throws : False -- Skip return : False foreign import ccall "soup_logger_new" soup_logger_new :: CUInt -> -- level : TInterface "Soup" "LoggerLogLevel" Int32 -> -- max_body_size : TBasicType TInt32 IO (Ptr Logger) loggerNew :: (MonadIO m) => LoggerLogLevel -> -- level Int32 -> -- max_body_size m Logger loggerNew level max_body_size = liftIO $ do let level' = (fromIntegral . fromEnum) level result <- soup_logger_new level' max_body_size checkUnexpectedReturnNULL "soup_logger_new" result result' <- (wrapObject Logger) result return result' -- method Logger::attach -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Logger", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "session", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Logger", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "session", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_logger_attach" soup_logger_attach :: Ptr Logger -> -- _obj : TInterface "Soup" "Logger" Ptr Session -> -- session : TInterface "Soup" "Session" IO () {-# DEPRECATED loggerAttach ["Use soup_session_add_feature() instead."]#-} loggerAttach :: (MonadIO m, LoggerK a, SessionK b) => a -> -- _obj b -> -- session m () loggerAttach _obj session = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let session' = unsafeManagedPtrCastPtr session soup_logger_attach _obj' session' touchManagedPtr _obj touchManagedPtr session return () -- method Logger::detach -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Logger", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "session", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Logger", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "session", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_logger_detach" soup_logger_detach :: Ptr Logger -> -- _obj : TInterface "Soup" "Logger" Ptr Session -> -- session : TInterface "Soup" "Session" IO () {-# DEPRECATED loggerDetach ["Use soup_session_remove_feature() instead."]#-} loggerDetach :: (MonadIO m, LoggerK a, SessionK b) => a -> -- _obj b -> -- session m () loggerDetach _obj session = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let session' = unsafeManagedPtrCastPtr session soup_logger_detach _obj' session' touchManagedPtr _obj touchManagedPtr session return () -- method Logger::set_printer -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Logger", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "printer", argType = TInterface "Soup" "LoggerPrinter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing},Arg {argName = "printer_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "destroy", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Logger", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "printer", argType = TInterface "Soup" "LoggerPrinter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_logger_set_printer" soup_logger_set_printer :: Ptr Logger -> -- _obj : TInterface "Soup" "Logger" FunPtr LoggerPrinterC -> -- printer : TInterface "Soup" "LoggerPrinter" Ptr () -> -- printer_data : TBasicType TVoid FunPtr GLib.DestroyNotifyC -> -- destroy : TInterface "GLib" "DestroyNotify" IO () loggerSetPrinter :: (MonadIO m, LoggerK a) => a -> -- _obj LoggerPrinter -> -- printer m () loggerSetPrinter _obj printer = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj printer' <- mkLoggerPrinter (loggerPrinterWrapper Nothing printer) let printer_data = castFunPtrToPtr printer' let destroy = safeFreeFunPtrPtr soup_logger_set_printer _obj' printer' printer_data destroy touchManagedPtr _obj return () -- method Logger::set_request_filter -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Logger", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "request_filter", argType = TInterface "Soup" "LoggerFilter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing},Arg {argName = "filter_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "destroy", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Logger", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "request_filter", argType = TInterface "Soup" "LoggerFilter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_logger_set_request_filter" soup_logger_set_request_filter :: Ptr Logger -> -- _obj : TInterface "Soup" "Logger" FunPtr LoggerFilterC -> -- request_filter : TInterface "Soup" "LoggerFilter" Ptr () -> -- filter_data : TBasicType TVoid FunPtr GLib.DestroyNotifyC -> -- destroy : TInterface "GLib" "DestroyNotify" IO () loggerSetRequestFilter :: (MonadIO m, LoggerK a) => a -> -- _obj LoggerFilter -> -- request_filter m () loggerSetRequestFilter _obj request_filter = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj request_filter' <- mkLoggerFilter (loggerFilterWrapper Nothing request_filter) let filter_data = castFunPtrToPtr request_filter' let destroy = safeFreeFunPtrPtr soup_logger_set_request_filter _obj' request_filter' filter_data destroy touchManagedPtr _obj return () -- method Logger::set_response_filter -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Logger", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "response_filter", argType = TInterface "Soup" "LoggerFilter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing},Arg {argName = "filter_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "destroy", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Logger", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "response_filter", argType = TInterface "Soup" "LoggerFilter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_logger_set_response_filter" soup_logger_set_response_filter :: Ptr Logger -> -- _obj : TInterface "Soup" "Logger" FunPtr LoggerFilterC -> -- response_filter : TInterface "Soup" "LoggerFilter" Ptr () -> -- filter_data : TBasicType TVoid FunPtr GLib.DestroyNotifyC -> -- destroy : TInterface "GLib" "DestroyNotify" IO () loggerSetResponseFilter :: (MonadIO m, LoggerK a) => a -> -- _obj LoggerFilter -> -- response_filter m () loggerSetResponseFilter _obj response_filter = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj response_filter' <- mkLoggerFilter (loggerFilterWrapper Nothing response_filter) let filter_data = castFunPtrToPtr response_filter' let destroy = safeFreeFunPtrPtr soup_logger_set_response_filter _obj' response_filter' filter_data destroy touchManagedPtr _obj return () -- callback LoggerFilter loggerFilterClosure :: LoggerFilter -> IO Closure loggerFilterClosure cb = newCClosure =<< mkLoggerFilter wrapped where wrapped = loggerFilterWrapper Nothing cb type LoggerFilterC = Ptr Logger -> Ptr Message -> Ptr () -> IO CUInt foreign import ccall "wrapper" mkLoggerFilter :: LoggerFilterC -> IO (FunPtr LoggerFilterC) type LoggerFilter = Logger -> Message -> IO LoggerLogLevel noLoggerFilter :: Maybe LoggerFilter noLoggerFilter = Nothing loggerFilterWrapper :: Maybe (Ptr (FunPtr (LoggerFilterC))) -> LoggerFilter -> Ptr Logger -> Ptr Message -> Ptr () -> IO CUInt loggerFilterWrapper funptrptr _cb logger msg _ = do logger' <- (newObject Logger) logger msg' <- (newObject Message) msg result <- _cb logger' msg' maybeReleaseFunPtr funptrptr let result' = (fromIntegral . fromEnum) result return result' -- Enum LoggerLogLevel data LoggerLogLevel = LoggerLogLevelNone | LoggerLogLevelMinimal | LoggerLogLevelHeaders | LoggerLogLevelBody | AnotherLoggerLogLevel Int deriving (Show, Eq) instance Enum LoggerLogLevel where fromEnum LoggerLogLevelNone = 0 fromEnum LoggerLogLevelMinimal = 1 fromEnum LoggerLogLevelHeaders = 2 fromEnum LoggerLogLevelBody = 3 fromEnum (AnotherLoggerLogLevel k) = k toEnum 0 = LoggerLogLevelNone toEnum 1 = LoggerLogLevelMinimal toEnum 2 = LoggerLogLevelHeaders toEnum 3 = LoggerLogLevelBody toEnum k = AnotherLoggerLogLevel k foreign import ccall "soup_logger_log_level_get_type" c_soup_logger_log_level_get_type :: IO GType instance BoxedEnum LoggerLogLevel where boxedEnumType _ = c_soup_logger_log_level_get_type -- callback LoggerPrinter loggerPrinterClosure :: LoggerPrinter -> IO Closure loggerPrinterClosure cb = newCClosure =<< mkLoggerPrinter wrapped where wrapped = loggerPrinterWrapper Nothing cb type LoggerPrinterC = Ptr Logger -> CUInt -> Int8 -> CString -> Ptr () -> IO () foreign import ccall "wrapper" mkLoggerPrinter :: LoggerPrinterC -> IO (FunPtr LoggerPrinterC) type LoggerPrinter = Logger -> LoggerLogLevel -> Int8 -> T.Text -> IO () noLoggerPrinter :: Maybe LoggerPrinter noLoggerPrinter = Nothing loggerPrinterWrapper :: Maybe (Ptr (FunPtr (LoggerPrinterC))) -> LoggerPrinter -> Ptr Logger -> CUInt -> Int8 -> CString -> Ptr () -> IO () loggerPrinterWrapper funptrptr _cb logger level direction data_ _ = do logger' <- (newObject Logger) logger let level' = (toEnum . fromIntegral) level data_' <- cstringToText data_ _cb logger' level' direction data_' maybeReleaseFunPtr funptrptr -- Enum MemoryUse data MemoryUse = MemoryUseStatic | MemoryUseTake | MemoryUseCopy | MemoryUseTemporary | AnotherMemoryUse Int deriving (Show, Eq) instance Enum MemoryUse where fromEnum MemoryUseStatic = 0 fromEnum MemoryUseTake = 1 fromEnum MemoryUseCopy = 2 fromEnum MemoryUseTemporary = 3 fromEnum (AnotherMemoryUse k) = k toEnum 0 = MemoryUseStatic toEnum 1 = MemoryUseTake toEnum 2 = MemoryUseCopy toEnum 3 = MemoryUseTemporary toEnum k = AnotherMemoryUse k foreign import ccall "soup_memory_use_get_type" c_soup_memory_use_get_type :: IO GType instance BoxedEnum MemoryUse where boxedEnumType _ = c_soup_memory_use_get_type -- object Message newtype Message = Message (ForeignPtr Message) noMessage :: Maybe Message noMessage = Nothing foreign import ccall "soup_message_get_type" c_soup_message_get_type :: IO GType type instance ParentTypes Message = '[GObject.Object] instance GObject Message where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_message_get_type class GObject o => MessageK o instance (GObject o, IsDescendantOf Message o) => MessageK o toMessage :: MessageK o => o -> IO Message toMessage = unsafeCastTo Message -- method Message::new -- method type : Constructor -- Args : [Arg {argName = "method", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "method", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Message" -- throws : False -- Skip return : False foreign import ccall "soup_message_new" soup_message_new :: CString -> -- method : TBasicType TUTF8 CString -> -- uri_string : TBasicType TUTF8 IO (Ptr Message) messageNew :: (MonadIO m) => T.Text -> -- method T.Text -> -- uri_string m Message messageNew method uri_string = liftIO $ do method' <- textToCString method uri_string' <- textToCString uri_string result <- soup_message_new method' uri_string' checkUnexpectedReturnNULL "soup_message_new" result result' <- (wrapObject Message) result freeMem method' freeMem uri_string' return result' -- method Message::new_from_uri -- method type : Constructor -- Args : [Arg {argName = "method", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "method", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Message" -- throws : False -- Skip return : False foreign import ccall "soup_message_new_from_uri" soup_message_new_from_uri :: CString -> -- method : TBasicType TUTF8 Ptr URI -> -- uri : TInterface "Soup" "URI" IO (Ptr Message) messageNewFromUri :: (MonadIO m) => T.Text -> -- method URI -> -- uri m Message messageNewFromUri method uri = liftIO $ do method' <- textToCString method let uri' = unsafeManagedPtrGetPtr uri result <- soup_message_new_from_uri method' uri' checkUnexpectedReturnNULL "soup_message_new_from_uri" result result' <- (wrapObject Message) result touchManagedPtr uri freeMem method' return result' -- method Message::content_sniffed -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", 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 TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", 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 TVoid) (TBasicType TVoid), 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_content_sniffed" soup_message_content_sniffed :: Ptr Message -> -- _obj : TInterface "Soup" "Message" CString -> -- content_type : TBasicType TUTF8 Ptr (GHashTable (Ptr ()) (Ptr ())) -> -- params : TGHash (TBasicType TVoid) (TBasicType TVoid) IO () messageContentSniffed :: (MonadIO m, MessageK a) => a -> -- _obj T.Text -> -- content_type Map.Map (Ptr ()) (Ptr ()) -> -- params m () messageContentSniffed _obj content_type params = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj content_type' <- textToCString content_type let params' = Map.toList params let params'' = mapFirst ptrPackPtr params' let params''' = mapSecond ptrPackPtr params'' params'''' <- packGHashTable gDirectHash gDirectEqual Nothing Nothing params''' soup_message_content_sniffed _obj' content_type' params'''' touchManagedPtr _obj freeMem content_type' unrefGHashTable params'''' return () -- method Message::disable_feature -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature_type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature_type", argType = TBasicType TGType, 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_disable_feature" soup_message_disable_feature :: Ptr Message -> -- _obj : TInterface "Soup" "Message" CGType -> -- feature_type : TBasicType TGType IO () messageDisableFeature :: (MonadIO m, MessageK a) => a -> -- _obj GType -> -- feature_type m () messageDisableFeature _obj feature_type = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let feature_type' = gtypeToCGType feature_type soup_message_disable_feature _obj' feature_type' touchManagedPtr _obj return () -- method Message::finished -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", 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_finished" soup_message_finished :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO () messageFinished :: (MonadIO m, MessageK a) => a -> -- _obj m () messageFinished _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_message_finished _obj' touchManagedPtr _obj return () -- method Message::get_address -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Address" -- throws : False -- Skip return : False foreign import ccall "soup_message_get_address" soup_message_get_address :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO (Ptr Address) messageGetAddress :: (MonadIO m, MessageK a) => a -> -- _obj m Address messageGetAddress _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_message_get_address _obj' checkUnexpectedReturnNULL "soup_message_get_address" result result' <- (newObject Address) result touchManagedPtr _obj return result' -- method Message::get_first_party -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "URI" -- throws : False -- Skip return : False foreign import ccall "soup_message_get_first_party" soup_message_get_first_party :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO (Ptr URI) messageGetFirstParty :: (MonadIO m, MessageK a) => a -> -- _obj m URI messageGetFirstParty _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_message_get_first_party _obj' checkUnexpectedReturnNULL "soup_message_get_first_party" result result' <- (newBoxed URI) result touchManagedPtr _obj return result' -- method Message::get_flags -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "MessageFlags" -- throws : False -- Skip return : False foreign import ccall "soup_message_get_flags" soup_message_get_flags :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO CUInt messageGetFlags :: (MonadIO m, MessageK a) => a -> -- _obj m [MessageFlags] messageGetFlags _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_message_get_flags _obj' let result' = wordToGFlags result touchManagedPtr _obj return result' -- method Message::get_http_version -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "HTTPVersion" -- throws : False -- Skip return : False foreign import ccall "soup_message_get_http_version" soup_message_get_http_version :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO CUInt messageGetHttpVersion :: (MonadIO m, MessageK a) => a -> -- _obj m HTTPVersion messageGetHttpVersion _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_message_get_http_version _obj' let result' = (toEnum . fromIntegral) result touchManagedPtr _obj return result' -- method Message::get_https_status -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "certificate", argType = TInterface "Gio" "TlsCertificate", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "errors", argType = TInterface "Gio" "TlsCertificateFlags", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", 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_get_https_status" soup_message_get_https_status :: Ptr Message -> -- _obj : TInterface "Soup" "Message" Ptr (Ptr Gio.TlsCertificate) -> -- certificate : TInterface "Gio" "TlsCertificate" Ptr CUInt -> -- errors : TInterface "Gio" "TlsCertificateFlags" IO CInt messageGetHttpsStatus :: (MonadIO m, MessageK a) => a -> -- _obj m (Bool,Gio.TlsCertificate,[Gio.TlsCertificateFlags]) messageGetHttpsStatus _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj certificate <- allocMem :: IO (Ptr (Ptr Gio.TlsCertificate)) errors <- allocMem :: IO (Ptr CUInt) result <- soup_message_get_https_status _obj' certificate errors let result' = (/= 0) result certificate' <- peek certificate certificate'' <- (newObject Gio.TlsCertificate) certificate' errors' <- peek errors let errors'' = wordToGFlags errors' touchManagedPtr _obj freeMem certificate freeMem errors return (result', certificate'', errors'') -- method Message::get_priority -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "MessagePriority" -- throws : False -- Skip return : False foreign import ccall "soup_message_get_priority" soup_message_get_priority :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO CUInt messageGetPriority :: (MonadIO m, MessageK a) => a -> -- _obj m MessagePriority messageGetPriority _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_message_get_priority _obj' let result' = (toEnum . fromIntegral) result touchManagedPtr _obj return result' -- method Message::get_soup_request -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Request" -- throws : False -- Skip return : False foreign import ccall "soup_message_get_soup_request" soup_message_get_soup_request :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO (Ptr Request) messageGetSoupRequest :: (MonadIO m, MessageK a) => a -> -- _obj m Request messageGetSoupRequest _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_message_get_soup_request _obj' checkUnexpectedReturnNULL "soup_message_get_soup_request" result result' <- (newObject Request) result touchManagedPtr _obj return result' -- method Message::get_uri -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "URI" -- throws : False -- Skip return : False foreign import ccall "soup_message_get_uri" soup_message_get_uri :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO (Ptr URI) messageGetUri :: (MonadIO m, MessageK a) => a -> -- _obj m URI messageGetUri _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_message_get_uri _obj' checkUnexpectedReturnNULL "soup_message_get_uri" result result' <- (newBoxed URI) result touchManagedPtr _obj return result' -- method Message::got_body -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", 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_got_body" soup_message_got_body :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO () messageGotBody :: (MonadIO m, MessageK a) => a -> -- _obj m () messageGotBody _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_message_got_body _obj' touchManagedPtr _obj return () -- method Message::got_chunk -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "chunk", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "chunk", argType = TInterface "Soup" "Buffer", 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_got_chunk" soup_message_got_chunk :: Ptr Message -> -- _obj : TInterface "Soup" "Message" Ptr Buffer -> -- chunk : TInterface "Soup" "Buffer" IO () messageGotChunk :: (MonadIO m, MessageK a) => a -> -- _obj Buffer -> -- chunk m () messageGotChunk _obj chunk = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let chunk' = unsafeManagedPtrGetPtr chunk soup_message_got_chunk _obj' chunk' touchManagedPtr _obj touchManagedPtr chunk return () -- method Message::got_headers -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", 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_got_headers" soup_message_got_headers :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO () messageGotHeaders :: (MonadIO m, MessageK a) => a -> -- _obj m () messageGotHeaders _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_message_got_headers _obj' touchManagedPtr _obj return () -- method Message::got_informational -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", 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_got_informational" soup_message_got_informational :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO () messageGotInformational :: (MonadIO m, MessageK a) => a -> -- _obj m () messageGotInformational _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_message_got_informational _obj' touchManagedPtr _obj return () -- method Message::is_keepalive -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", 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_is_keepalive" soup_message_is_keepalive :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO CInt messageIsKeepalive :: (MonadIO m, MessageK a) => a -> -- _obj m Bool messageIsKeepalive _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_message_is_keepalive _obj' let result' = (/= 0) result touchManagedPtr _obj return result' -- method Message::restarted -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", 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_restarted" soup_message_restarted :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO () messageRestarted :: (MonadIO m, MessageK a) => a -> -- _obj m () messageRestarted _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_message_restarted _obj' touchManagedPtr _obj return () -- method Message::set_chunk_allocator -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "allocator", argType = TInterface "Soup" "ChunkAllocator", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "destroy_notify", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "allocator", argType = TInterface "Soup" "ChunkAllocator", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_message_set_chunk_allocator" soup_message_set_chunk_allocator :: Ptr Message -> -- _obj : TInterface "Soup" "Message" FunPtr ChunkAllocatorC -> -- allocator : TInterface "Soup" "ChunkAllocator" Ptr () -> -- user_data : TBasicType TVoid FunPtr GLib.DestroyNotifyC -> -- destroy_notify : TInterface "GLib" "DestroyNotify" IO () {-# DEPRECATED messageSetChunkAllocator ["#SoupRequest provides a much simpler API that lets you","read the response directly into your own buffers without needing to","mess with callbacks, pausing/unpausing, etc."]#-} messageSetChunkAllocator :: (MonadIO m, MessageK a) => a -> -- _obj ChunkAllocator -> -- allocator m () messageSetChunkAllocator _obj allocator = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj allocator' <- mkChunkAllocator (chunkAllocatorWrapper Nothing allocator) let user_data = castFunPtrToPtr allocator' let destroy_notify = safeFreeFunPtrPtr soup_message_set_chunk_allocator _obj' allocator' user_data destroy_notify touchManagedPtr _obj return () -- method Message::set_first_party -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "first_party", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "first_party", argType = TInterface "Soup" "URI", 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_set_first_party" soup_message_set_first_party :: Ptr Message -> -- _obj : TInterface "Soup" "Message" Ptr URI -> -- first_party : TInterface "Soup" "URI" IO () messageSetFirstParty :: (MonadIO m, MessageK a) => a -> -- _obj URI -> -- first_party m () messageSetFirstParty _obj first_party = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let first_party' = unsafeManagedPtrGetPtr first_party soup_message_set_first_party _obj' first_party' touchManagedPtr _obj touchManagedPtr first_party return () -- method Message::set_flags -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "Soup" "MessageFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "Soup" "MessageFlags", 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_set_flags" soup_message_set_flags :: Ptr Message -> -- _obj : TInterface "Soup" "Message" CUInt -> -- flags : TInterface "Soup" "MessageFlags" IO () messageSetFlags :: (MonadIO m, MessageK a) => a -> -- _obj [MessageFlags] -> -- flags m () messageSetFlags _obj flags = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let flags' = gflagsToWord flags soup_message_set_flags _obj' flags' touchManagedPtr _obj return () -- method Message::set_http_version -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "version", argType = TInterface "Soup" "HTTPVersion", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "version", argType = TInterface "Soup" "HTTPVersion", 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_set_http_version" soup_message_set_http_version :: Ptr Message -> -- _obj : TInterface "Soup" "Message" CUInt -> -- version : TInterface "Soup" "HTTPVersion" IO () messageSetHttpVersion :: (MonadIO m, MessageK a) => a -> -- _obj HTTPVersion -> -- version m () messageSetHttpVersion _obj version = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let version' = (fromIntegral . fromEnum) version soup_message_set_http_version _obj' version' touchManagedPtr _obj return () -- method Message::set_priority -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "priority", argType = TInterface "Soup" "MessagePriority", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "priority", argType = TInterface "Soup" "MessagePriority", 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_set_priority" soup_message_set_priority :: Ptr Message -> -- _obj : TInterface "Soup" "Message" CUInt -> -- priority : TInterface "Soup" "MessagePriority" IO () messageSetPriority :: (MonadIO m, MessageK a) => a -> -- _obj MessagePriority -> -- priority m () messageSetPriority _obj priority = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let priority' = (fromIntegral . fromEnum) priority soup_message_set_priority _obj' priority' touchManagedPtr _obj return () -- method Message::set_redirect -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "status_code", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "redirect_uri", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "status_code", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "redirect_uri", 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_set_redirect" soup_message_set_redirect :: Ptr Message -> -- _obj : TInterface "Soup" "Message" Word32 -> -- status_code : TBasicType TUInt32 CString -> -- redirect_uri : TBasicType TUTF8 IO () messageSetRedirect :: (MonadIO m, MessageK a) => a -> -- _obj Word32 -> -- status_code T.Text -> -- redirect_uri m () messageSetRedirect _obj status_code redirect_uri = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj redirect_uri' <- textToCString redirect_uri soup_message_set_redirect _obj' status_code redirect_uri' touchManagedPtr _obj freeMem redirect_uri' return () -- method Message::set_request -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "content_type", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "req_use", argType = TInterface "Soup" "MemoryUse", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "req_body", argType = TCArray False (-1) 4 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "req_length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [Arg {argName = "req_length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "content_type", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "req_use", argType = TInterface "Soup" "MemoryUse", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "req_body", argType = TCArray False (-1) 4 (TBasicType TUInt8), 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_set_request" soup_message_set_request :: Ptr Message -> -- _obj : TInterface "Soup" "Message" CString -> -- content_type : TBasicType TUTF8 CUInt -> -- req_use : TInterface "Soup" "MemoryUse" Ptr Word8 -> -- req_body : TCArray False (-1) 4 (TBasicType TUInt8) Word64 -> -- req_length : TBasicType TUInt64 IO () messageSetRequest :: (MonadIO m, MessageK a) => a -> -- _obj Maybe (T.Text) -> -- content_type MemoryUse -> -- req_use Maybe (ByteString) -> -- req_body m () messageSetRequest _obj content_type req_use req_body = liftIO $ do let req_length = case req_body of Nothing -> 0 Just jReq_body -> fromIntegral $ B.length jReq_body let _obj' = unsafeManagedPtrCastPtr _obj maybeContent_type <- case content_type of Nothing -> return nullPtr Just jContent_type -> do jContent_type' <- textToCString jContent_type return jContent_type' let req_use' = (fromIntegral . fromEnum) req_use maybeReq_body <- case req_body of Nothing -> return nullPtr Just jReq_body -> do jReq_body' <- packByteString jReq_body return jReq_body' soup_message_set_request _obj' maybeContent_type req_use' maybeReq_body req_length touchManagedPtr _obj freeMem maybeContent_type freeMem maybeReq_body return () -- method Message::set_response -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "content_type", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "resp_use", argType = TInterface "Soup" "MemoryUse", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "resp_body", argType = TCArray False (-1) 4 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "resp_length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [Arg {argName = "resp_length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "content_type", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "resp_use", argType = TInterface "Soup" "MemoryUse", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "resp_body", argType = TCArray False (-1) 4 (TBasicType TUInt8), 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_set_response" soup_message_set_response :: Ptr Message -> -- _obj : TInterface "Soup" "Message" CString -> -- content_type : TBasicType TUTF8 CUInt -> -- resp_use : TInterface "Soup" "MemoryUse" Ptr Word8 -> -- resp_body : TCArray False (-1) 4 (TBasicType TUInt8) Word64 -> -- resp_length : TBasicType TUInt64 IO () messageSetResponse :: (MonadIO m, MessageK a) => a -> -- _obj Maybe (T.Text) -> -- content_type MemoryUse -> -- resp_use Maybe (ByteString) -> -- resp_body m () messageSetResponse _obj content_type resp_use resp_body = liftIO $ do let resp_length = case resp_body of Nothing -> 0 Just jResp_body -> fromIntegral $ B.length jResp_body let _obj' = unsafeManagedPtrCastPtr _obj maybeContent_type <- case content_type of Nothing -> return nullPtr Just jContent_type -> do jContent_type' <- textToCString jContent_type return jContent_type' let resp_use' = (fromIntegral . fromEnum) resp_use maybeResp_body <- case resp_body of Nothing -> return nullPtr Just jResp_body -> do jResp_body' <- packByteString jResp_body return jResp_body' soup_message_set_response _obj' maybeContent_type resp_use' maybeResp_body resp_length touchManagedPtr _obj freeMem maybeContent_type freeMem maybeResp_body return () -- method Message::set_status -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "status_code", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "status_code", argType = TBasicType TUInt32, 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_set_status" soup_message_set_status :: Ptr Message -> -- _obj : TInterface "Soup" "Message" Word32 -> -- status_code : TBasicType TUInt32 IO () messageSetStatus :: (MonadIO m, MessageK a) => a -> -- _obj Word32 -> -- status_code m () messageSetStatus _obj status_code = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_message_set_status _obj' status_code touchManagedPtr _obj return () -- method Message::set_status_full -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "status_code", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "reason_phrase", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "status_code", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "reason_phrase", 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_set_status_full" soup_message_set_status_full :: Ptr Message -> -- _obj : TInterface "Soup" "Message" Word32 -> -- status_code : TBasicType TUInt32 CString -> -- reason_phrase : TBasicType TUTF8 IO () messageSetStatusFull :: (MonadIO m, MessageK a) => a -> -- _obj Word32 -> -- status_code T.Text -> -- reason_phrase m () messageSetStatusFull _obj status_code reason_phrase = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj reason_phrase' <- textToCString reason_phrase soup_message_set_status_full _obj' status_code reason_phrase' touchManagedPtr _obj freeMem reason_phrase' return () -- method Message::set_uri -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", 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_set_uri" soup_message_set_uri :: Ptr Message -> -- _obj : TInterface "Soup" "Message" Ptr URI -> -- uri : TInterface "Soup" "URI" IO () messageSetUri :: (MonadIO m, MessageK a) => a -> -- _obj URI -> -- uri m () messageSetUri _obj uri = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let uri' = unsafeManagedPtrGetPtr uri soup_message_set_uri _obj' uri' touchManagedPtr _obj touchManagedPtr uri return () -- method Message::starting -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", 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_starting" soup_message_starting :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO () messageStarting :: (MonadIO m, MessageK a) => a -> -- _obj m () messageStarting _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_message_starting _obj' touchManagedPtr _obj return () -- method Message::wrote_body -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", 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_wrote_body" soup_message_wrote_body :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO () messageWroteBody :: (MonadIO m, MessageK a) => a -> -- _obj m () messageWroteBody _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_message_wrote_body _obj' touchManagedPtr _obj return () -- method Message::wrote_body_data -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "chunk", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "chunk", argType = TInterface "Soup" "Buffer", 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_wrote_body_data" soup_message_wrote_body_data :: Ptr Message -> -- _obj : TInterface "Soup" "Message" Ptr Buffer -> -- chunk : TInterface "Soup" "Buffer" IO () messageWroteBodyData :: (MonadIO m, MessageK a) => a -> -- _obj Buffer -> -- chunk m () messageWroteBodyData _obj chunk = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let chunk' = unsafeManagedPtrGetPtr chunk soup_message_wrote_body_data _obj' chunk' touchManagedPtr _obj touchManagedPtr chunk return () -- method Message::wrote_chunk -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", 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_wrote_chunk" soup_message_wrote_chunk :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO () messageWroteChunk :: (MonadIO m, MessageK a) => a -> -- _obj m () messageWroteChunk _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_message_wrote_chunk _obj' touchManagedPtr _obj return () -- method Message::wrote_headers -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", 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_wrote_headers" soup_message_wrote_headers :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO () messageWroteHeaders :: (MonadIO m, MessageK a) => a -> -- _obj m () messageWroteHeaders _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_message_wrote_headers _obj' touchManagedPtr _obj return () -- method Message::wrote_informational -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Message", 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_wrote_informational" soup_message_wrote_informational :: Ptr Message -> -- _obj : TInterface "Soup" "Message" IO () messageWroteInformational :: (MonadIO m, MessageK a) => a -> -- _obj m () messageWroteInformational _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_message_wrote_informational _obj' touchManagedPtr _obj return () -- signal Message::content-sniffed type MessageContentSniffedCallback = T.Text -> Map.Map T.Text T.Text -> IO () noMessageContentSniffedCallback :: Maybe MessageContentSniffedCallback noMessageContentSniffedCallback = Nothing type MessageContentSniffedCallbackC = Ptr () -> -- object CString -> Ptr (GHashTable CString CString) -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkMessageContentSniffedCallback :: MessageContentSniffedCallbackC -> IO (FunPtr MessageContentSniffedCallbackC) messageContentSniffedClosure :: MessageContentSniffedCallback -> IO Closure messageContentSniffedClosure cb = newCClosure =<< mkMessageContentSniffedCallback wrapped where wrapped = messageContentSniffedCallbackWrapper cb messageContentSniffedCallbackWrapper :: MessageContentSniffedCallback -> Ptr () -> CString -> Ptr (GHashTable CString CString) -> Ptr () -> IO () messageContentSniffedCallbackWrapper _cb _ type_ params _ = do type_' <- cstringToText type_ 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''''' _cb type_' params'''''' onMessageContentSniffed :: (GObject a, MonadIO m) => a -> MessageContentSniffedCallback -> m SignalHandlerId onMessageContentSniffed obj cb = liftIO $ connectMessageContentSniffed obj cb SignalConnectBefore afterMessageContentSniffed :: (GObject a, MonadIO m) => a -> MessageContentSniffedCallback -> m SignalHandlerId afterMessageContentSniffed obj cb = connectMessageContentSniffed obj cb SignalConnectAfter connectMessageContentSniffed :: (GObject a, MonadIO m) => a -> MessageContentSniffedCallback -> SignalConnectMode -> m SignalHandlerId connectMessageContentSniffed obj cb after = liftIO $ do cb' <- mkMessageContentSniffedCallback (messageContentSniffedCallbackWrapper cb) connectSignalFunPtr obj "content-sniffed" cb' after -- signal Message::finished type MessageFinishedCallback = IO () noMessageFinishedCallback :: Maybe MessageFinishedCallback noMessageFinishedCallback = Nothing type MessageFinishedCallbackC = Ptr () -> -- object Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkMessageFinishedCallback :: MessageFinishedCallbackC -> IO (FunPtr MessageFinishedCallbackC) messageFinishedClosure :: MessageFinishedCallback -> IO Closure messageFinishedClosure cb = newCClosure =<< mkMessageFinishedCallback wrapped where wrapped = messageFinishedCallbackWrapper cb messageFinishedCallbackWrapper :: MessageFinishedCallback -> Ptr () -> Ptr () -> IO () messageFinishedCallbackWrapper _cb _ _ = do _cb onMessageFinished :: (GObject a, MonadIO m) => a -> MessageFinishedCallback -> m SignalHandlerId onMessageFinished obj cb = liftIO $ connectMessageFinished obj cb SignalConnectBefore afterMessageFinished :: (GObject a, MonadIO m) => a -> MessageFinishedCallback -> m SignalHandlerId afterMessageFinished obj cb = connectMessageFinished obj cb SignalConnectAfter connectMessageFinished :: (GObject a, MonadIO m) => a -> MessageFinishedCallback -> SignalConnectMode -> m SignalHandlerId connectMessageFinished obj cb after = liftIO $ do cb' <- mkMessageFinishedCallback (messageFinishedCallbackWrapper cb) connectSignalFunPtr obj "finished" cb' after -- signal Message::got-body type MessageGotBodyCallback = IO () noMessageGotBodyCallback :: Maybe MessageGotBodyCallback noMessageGotBodyCallback = Nothing type MessageGotBodyCallbackC = Ptr () -> -- object Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkMessageGotBodyCallback :: MessageGotBodyCallbackC -> IO (FunPtr MessageGotBodyCallbackC) messageGotBodyClosure :: MessageGotBodyCallback -> IO Closure messageGotBodyClosure cb = newCClosure =<< mkMessageGotBodyCallback wrapped where wrapped = messageGotBodyCallbackWrapper cb messageGotBodyCallbackWrapper :: MessageGotBodyCallback -> Ptr () -> Ptr () -> IO () messageGotBodyCallbackWrapper _cb _ _ = do _cb onMessageGotBody :: (GObject a, MonadIO m) => a -> MessageGotBodyCallback -> m SignalHandlerId onMessageGotBody obj cb = liftIO $ connectMessageGotBody obj cb SignalConnectBefore afterMessageGotBody :: (GObject a, MonadIO m) => a -> MessageGotBodyCallback -> m SignalHandlerId afterMessageGotBody obj cb = connectMessageGotBody obj cb SignalConnectAfter connectMessageGotBody :: (GObject a, MonadIO m) => a -> MessageGotBodyCallback -> SignalConnectMode -> m SignalHandlerId connectMessageGotBody obj cb after = liftIO $ do cb' <- mkMessageGotBodyCallback (messageGotBodyCallbackWrapper cb) connectSignalFunPtr obj "got-body" cb' after -- signal Message::got-chunk type MessageGotChunkCallback = Buffer -> IO () noMessageGotChunkCallback :: Maybe MessageGotChunkCallback noMessageGotChunkCallback = Nothing type MessageGotChunkCallbackC = Ptr () -> -- object Ptr Buffer -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkMessageGotChunkCallback :: MessageGotChunkCallbackC -> IO (FunPtr MessageGotChunkCallbackC) messageGotChunkClosure :: MessageGotChunkCallback -> IO Closure messageGotChunkClosure cb = newCClosure =<< mkMessageGotChunkCallback wrapped where wrapped = messageGotChunkCallbackWrapper cb messageGotChunkCallbackWrapper :: MessageGotChunkCallback -> Ptr () -> Ptr Buffer -> Ptr () -> IO () messageGotChunkCallbackWrapper _cb _ chunk _ = do chunk' <- (newBoxed Buffer) chunk _cb chunk' onMessageGotChunk :: (GObject a, MonadIO m) => a -> MessageGotChunkCallback -> m SignalHandlerId onMessageGotChunk obj cb = liftIO $ connectMessageGotChunk obj cb SignalConnectBefore afterMessageGotChunk :: (GObject a, MonadIO m) => a -> MessageGotChunkCallback -> m SignalHandlerId afterMessageGotChunk obj cb = connectMessageGotChunk obj cb SignalConnectAfter connectMessageGotChunk :: (GObject a, MonadIO m) => a -> MessageGotChunkCallback -> SignalConnectMode -> m SignalHandlerId connectMessageGotChunk obj cb after = liftIO $ do cb' <- mkMessageGotChunkCallback (messageGotChunkCallbackWrapper cb) connectSignalFunPtr obj "got-chunk" cb' after -- signal Message::got-headers type MessageGotHeadersCallback = IO () noMessageGotHeadersCallback :: Maybe MessageGotHeadersCallback noMessageGotHeadersCallback = Nothing type MessageGotHeadersCallbackC = Ptr () -> -- object Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkMessageGotHeadersCallback :: MessageGotHeadersCallbackC -> IO (FunPtr MessageGotHeadersCallbackC) messageGotHeadersClosure :: MessageGotHeadersCallback -> IO Closure messageGotHeadersClosure cb = newCClosure =<< mkMessageGotHeadersCallback wrapped where wrapped = messageGotHeadersCallbackWrapper cb messageGotHeadersCallbackWrapper :: MessageGotHeadersCallback -> Ptr () -> Ptr () -> IO () messageGotHeadersCallbackWrapper _cb _ _ = do _cb onMessageGotHeaders :: (GObject a, MonadIO m) => a -> MessageGotHeadersCallback -> m SignalHandlerId onMessageGotHeaders obj cb = liftIO $ connectMessageGotHeaders obj cb SignalConnectBefore afterMessageGotHeaders :: (GObject a, MonadIO m) => a -> MessageGotHeadersCallback -> m SignalHandlerId afterMessageGotHeaders obj cb = connectMessageGotHeaders obj cb SignalConnectAfter connectMessageGotHeaders :: (GObject a, MonadIO m) => a -> MessageGotHeadersCallback -> SignalConnectMode -> m SignalHandlerId connectMessageGotHeaders obj cb after = liftIO $ do cb' <- mkMessageGotHeadersCallback (messageGotHeadersCallbackWrapper cb) connectSignalFunPtr obj "got-headers" cb' after -- signal Message::got-informational type MessageGotInformationalCallback = IO () noMessageGotInformationalCallback :: Maybe MessageGotInformationalCallback noMessageGotInformationalCallback = Nothing type MessageGotInformationalCallbackC = Ptr () -> -- object Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkMessageGotInformationalCallback :: MessageGotInformationalCallbackC -> IO (FunPtr MessageGotInformationalCallbackC) messageGotInformationalClosure :: MessageGotInformationalCallback -> IO Closure messageGotInformationalClosure cb = newCClosure =<< mkMessageGotInformationalCallback wrapped where wrapped = messageGotInformationalCallbackWrapper cb messageGotInformationalCallbackWrapper :: MessageGotInformationalCallback -> Ptr () -> Ptr () -> IO () messageGotInformationalCallbackWrapper _cb _ _ = do _cb onMessageGotInformational :: (GObject a, MonadIO m) => a -> MessageGotInformationalCallback -> m SignalHandlerId onMessageGotInformational obj cb = liftIO $ connectMessageGotInformational obj cb SignalConnectBefore afterMessageGotInformational :: (GObject a, MonadIO m) => a -> MessageGotInformationalCallback -> m SignalHandlerId afterMessageGotInformational obj cb = connectMessageGotInformational obj cb SignalConnectAfter connectMessageGotInformational :: (GObject a, MonadIO m) => a -> MessageGotInformationalCallback -> SignalConnectMode -> m SignalHandlerId connectMessageGotInformational obj cb after = liftIO $ do cb' <- mkMessageGotInformationalCallback (messageGotInformationalCallbackWrapper cb) connectSignalFunPtr obj "got-informational" cb' after -- signal Message::network-event type MessageNetworkEventCallback = Gio.SocketClientEvent -> Gio.IOStream -> IO () noMessageNetworkEventCallback :: Maybe MessageNetworkEventCallback noMessageNetworkEventCallback = Nothing type MessageNetworkEventCallbackC = Ptr () -> -- object CUInt -> Ptr Gio.IOStream -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkMessageNetworkEventCallback :: MessageNetworkEventCallbackC -> IO (FunPtr MessageNetworkEventCallbackC) messageNetworkEventClosure :: MessageNetworkEventCallback -> IO Closure messageNetworkEventClosure cb = newCClosure =<< mkMessageNetworkEventCallback wrapped where wrapped = messageNetworkEventCallbackWrapper cb messageNetworkEventCallbackWrapper :: MessageNetworkEventCallback -> Ptr () -> CUInt -> Ptr Gio.IOStream -> Ptr () -> IO () messageNetworkEventCallbackWrapper _cb _ event connection _ = do let event' = (toEnum . fromIntegral) event connection' <- (newObject Gio.IOStream) connection _cb event' connection' onMessageNetworkEvent :: (GObject a, MonadIO m) => a -> MessageNetworkEventCallback -> m SignalHandlerId onMessageNetworkEvent obj cb = liftIO $ connectMessageNetworkEvent obj cb SignalConnectBefore afterMessageNetworkEvent :: (GObject a, MonadIO m) => a -> MessageNetworkEventCallback -> m SignalHandlerId afterMessageNetworkEvent obj cb = connectMessageNetworkEvent obj cb SignalConnectAfter connectMessageNetworkEvent :: (GObject a, MonadIO m) => a -> MessageNetworkEventCallback -> SignalConnectMode -> m SignalHandlerId connectMessageNetworkEvent obj cb after = liftIO $ do cb' <- mkMessageNetworkEventCallback (messageNetworkEventCallbackWrapper cb) connectSignalFunPtr obj "network-event" cb' after -- signal Message::restarted type MessageRestartedCallback = IO () noMessageRestartedCallback :: Maybe MessageRestartedCallback noMessageRestartedCallback = Nothing type MessageRestartedCallbackC = Ptr () -> -- object Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkMessageRestartedCallback :: MessageRestartedCallbackC -> IO (FunPtr MessageRestartedCallbackC) messageRestartedClosure :: MessageRestartedCallback -> IO Closure messageRestartedClosure cb = newCClosure =<< mkMessageRestartedCallback wrapped where wrapped = messageRestartedCallbackWrapper cb messageRestartedCallbackWrapper :: MessageRestartedCallback -> Ptr () -> Ptr () -> IO () messageRestartedCallbackWrapper _cb _ _ = do _cb onMessageRestarted :: (GObject a, MonadIO m) => a -> MessageRestartedCallback -> m SignalHandlerId onMessageRestarted obj cb = liftIO $ connectMessageRestarted obj cb SignalConnectBefore afterMessageRestarted :: (GObject a, MonadIO m) => a -> MessageRestartedCallback -> m SignalHandlerId afterMessageRestarted obj cb = connectMessageRestarted obj cb SignalConnectAfter connectMessageRestarted :: (GObject a, MonadIO m) => a -> MessageRestartedCallback -> SignalConnectMode -> m SignalHandlerId connectMessageRestarted obj cb after = liftIO $ do cb' <- mkMessageRestartedCallback (messageRestartedCallbackWrapper cb) connectSignalFunPtr obj "restarted" cb' after -- signal Message::starting type MessageStartingCallback = IO () noMessageStartingCallback :: Maybe MessageStartingCallback noMessageStartingCallback = Nothing type MessageStartingCallbackC = Ptr () -> -- object Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkMessageStartingCallback :: MessageStartingCallbackC -> IO (FunPtr MessageStartingCallbackC) messageStartingClosure :: MessageStartingCallback -> IO Closure messageStartingClosure cb = newCClosure =<< mkMessageStartingCallback wrapped where wrapped = messageStartingCallbackWrapper cb messageStartingCallbackWrapper :: MessageStartingCallback -> Ptr () -> Ptr () -> IO () messageStartingCallbackWrapper _cb _ _ = do _cb onMessageStarting :: (GObject a, MonadIO m) => a -> MessageStartingCallback -> m SignalHandlerId onMessageStarting obj cb = liftIO $ connectMessageStarting obj cb SignalConnectBefore afterMessageStarting :: (GObject a, MonadIO m) => a -> MessageStartingCallback -> m SignalHandlerId afterMessageStarting obj cb = connectMessageStarting obj cb SignalConnectAfter connectMessageStarting :: (GObject a, MonadIO m) => a -> MessageStartingCallback -> SignalConnectMode -> m SignalHandlerId connectMessageStarting obj cb after = liftIO $ do cb' <- mkMessageStartingCallback (messageStartingCallbackWrapper cb) connectSignalFunPtr obj "starting" cb' after -- signal Message::wrote-body type MessageWroteBodyCallback = IO () noMessageWroteBodyCallback :: Maybe MessageWroteBodyCallback noMessageWroteBodyCallback = Nothing type MessageWroteBodyCallbackC = Ptr () -> -- object Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkMessageWroteBodyCallback :: MessageWroteBodyCallbackC -> IO (FunPtr MessageWroteBodyCallbackC) messageWroteBodyClosure :: MessageWroteBodyCallback -> IO Closure messageWroteBodyClosure cb = newCClosure =<< mkMessageWroteBodyCallback wrapped where wrapped = messageWroteBodyCallbackWrapper cb messageWroteBodyCallbackWrapper :: MessageWroteBodyCallback -> Ptr () -> Ptr () -> IO () messageWroteBodyCallbackWrapper _cb _ _ = do _cb onMessageWroteBody :: (GObject a, MonadIO m) => a -> MessageWroteBodyCallback -> m SignalHandlerId onMessageWroteBody obj cb = liftIO $ connectMessageWroteBody obj cb SignalConnectBefore afterMessageWroteBody :: (GObject a, MonadIO m) => a -> MessageWroteBodyCallback -> m SignalHandlerId afterMessageWroteBody obj cb = connectMessageWroteBody obj cb SignalConnectAfter connectMessageWroteBody :: (GObject a, MonadIO m) => a -> MessageWroteBodyCallback -> SignalConnectMode -> m SignalHandlerId connectMessageWroteBody obj cb after = liftIO $ do cb' <- mkMessageWroteBodyCallback (messageWroteBodyCallbackWrapper cb) connectSignalFunPtr obj "wrote-body" cb' after -- signal Message::wrote-body-data type MessageWroteBodyDataCallback = Buffer -> IO () noMessageWroteBodyDataCallback :: Maybe MessageWroteBodyDataCallback noMessageWroteBodyDataCallback = Nothing type MessageWroteBodyDataCallbackC = Ptr () -> -- object Ptr Buffer -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkMessageWroteBodyDataCallback :: MessageWroteBodyDataCallbackC -> IO (FunPtr MessageWroteBodyDataCallbackC) messageWroteBodyDataClosure :: MessageWroteBodyDataCallback -> IO Closure messageWroteBodyDataClosure cb = newCClosure =<< mkMessageWroteBodyDataCallback wrapped where wrapped = messageWroteBodyDataCallbackWrapper cb messageWroteBodyDataCallbackWrapper :: MessageWroteBodyDataCallback -> Ptr () -> Ptr Buffer -> Ptr () -> IO () messageWroteBodyDataCallbackWrapper _cb _ chunk _ = do chunk' <- (newBoxed Buffer) chunk _cb chunk' onMessageWroteBodyData :: (GObject a, MonadIO m) => a -> MessageWroteBodyDataCallback -> m SignalHandlerId onMessageWroteBodyData obj cb = liftIO $ connectMessageWroteBodyData obj cb SignalConnectBefore afterMessageWroteBodyData :: (GObject a, MonadIO m) => a -> MessageWroteBodyDataCallback -> m SignalHandlerId afterMessageWroteBodyData obj cb = connectMessageWroteBodyData obj cb SignalConnectAfter connectMessageWroteBodyData :: (GObject a, MonadIO m) => a -> MessageWroteBodyDataCallback -> SignalConnectMode -> m SignalHandlerId connectMessageWroteBodyData obj cb after = liftIO $ do cb' <- mkMessageWroteBodyDataCallback (messageWroteBodyDataCallbackWrapper cb) connectSignalFunPtr obj "wrote-body-data" cb' after -- signal Message::wrote-chunk type MessageWroteChunkCallback = IO () noMessageWroteChunkCallback :: Maybe MessageWroteChunkCallback noMessageWroteChunkCallback = Nothing type MessageWroteChunkCallbackC = Ptr () -> -- object Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkMessageWroteChunkCallback :: MessageWroteChunkCallbackC -> IO (FunPtr MessageWroteChunkCallbackC) messageWroteChunkClosure :: MessageWroteChunkCallback -> IO Closure messageWroteChunkClosure cb = newCClosure =<< mkMessageWroteChunkCallback wrapped where wrapped = messageWroteChunkCallbackWrapper cb messageWroteChunkCallbackWrapper :: MessageWroteChunkCallback -> Ptr () -> Ptr () -> IO () messageWroteChunkCallbackWrapper _cb _ _ = do _cb onMessageWroteChunk :: (GObject a, MonadIO m) => a -> MessageWroteChunkCallback -> m SignalHandlerId onMessageWroteChunk obj cb = liftIO $ connectMessageWroteChunk obj cb SignalConnectBefore afterMessageWroteChunk :: (GObject a, MonadIO m) => a -> MessageWroteChunkCallback -> m SignalHandlerId afterMessageWroteChunk obj cb = connectMessageWroteChunk obj cb SignalConnectAfter connectMessageWroteChunk :: (GObject a, MonadIO m) => a -> MessageWroteChunkCallback -> SignalConnectMode -> m SignalHandlerId connectMessageWroteChunk obj cb after = liftIO $ do cb' <- mkMessageWroteChunkCallback (messageWroteChunkCallbackWrapper cb) connectSignalFunPtr obj "wrote-chunk" cb' after -- signal Message::wrote-headers type MessageWroteHeadersCallback = IO () noMessageWroteHeadersCallback :: Maybe MessageWroteHeadersCallback noMessageWroteHeadersCallback = Nothing type MessageWroteHeadersCallbackC = Ptr () -> -- object Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkMessageWroteHeadersCallback :: MessageWroteHeadersCallbackC -> IO (FunPtr MessageWroteHeadersCallbackC) messageWroteHeadersClosure :: MessageWroteHeadersCallback -> IO Closure messageWroteHeadersClosure cb = newCClosure =<< mkMessageWroteHeadersCallback wrapped where wrapped = messageWroteHeadersCallbackWrapper cb messageWroteHeadersCallbackWrapper :: MessageWroteHeadersCallback -> Ptr () -> Ptr () -> IO () messageWroteHeadersCallbackWrapper _cb _ _ = do _cb onMessageWroteHeaders :: (GObject a, MonadIO m) => a -> MessageWroteHeadersCallback -> m SignalHandlerId onMessageWroteHeaders obj cb = liftIO $ connectMessageWroteHeaders obj cb SignalConnectBefore afterMessageWroteHeaders :: (GObject a, MonadIO m) => a -> MessageWroteHeadersCallback -> m SignalHandlerId afterMessageWroteHeaders obj cb = connectMessageWroteHeaders obj cb SignalConnectAfter connectMessageWroteHeaders :: (GObject a, MonadIO m) => a -> MessageWroteHeadersCallback -> SignalConnectMode -> m SignalHandlerId connectMessageWroteHeaders obj cb after = liftIO $ do cb' <- mkMessageWroteHeadersCallback (messageWroteHeadersCallbackWrapper cb) connectSignalFunPtr obj "wrote-headers" cb' after -- signal Message::wrote-informational type MessageWroteInformationalCallback = IO () noMessageWroteInformationalCallback :: Maybe MessageWroteInformationalCallback noMessageWroteInformationalCallback = Nothing type MessageWroteInformationalCallbackC = Ptr () -> -- object Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkMessageWroteInformationalCallback :: MessageWroteInformationalCallbackC -> IO (FunPtr MessageWroteInformationalCallbackC) messageWroteInformationalClosure :: MessageWroteInformationalCallback -> IO Closure messageWroteInformationalClosure cb = newCClosure =<< mkMessageWroteInformationalCallback wrapped where wrapped = messageWroteInformationalCallbackWrapper cb messageWroteInformationalCallbackWrapper :: MessageWroteInformationalCallback -> Ptr () -> Ptr () -> IO () messageWroteInformationalCallbackWrapper _cb _ _ = do _cb onMessageWroteInformational :: (GObject a, MonadIO m) => a -> MessageWroteInformationalCallback -> m SignalHandlerId onMessageWroteInformational obj cb = liftIO $ connectMessageWroteInformational obj cb SignalConnectBefore afterMessageWroteInformational :: (GObject a, MonadIO m) => a -> MessageWroteInformationalCallback -> m SignalHandlerId afterMessageWroteInformational obj cb = connectMessageWroteInformational obj cb SignalConnectAfter connectMessageWroteInformational :: (GObject a, MonadIO m) => a -> MessageWroteInformationalCallback -> SignalConnectMode -> m SignalHandlerId connectMessageWroteInformational obj cb after = liftIO $ do cb' <- mkMessageWroteInformationalCallback (messageWroteInformationalCallbackWrapper cb) connectSignalFunPtr obj "wrote-informational" cb' after -- struct MessageBody newtype MessageBody = MessageBody (ForeignPtr MessageBody) noMessageBody :: Maybe MessageBody noMessageBody = Nothing foreign import ccall "soup_message_body_get_type" c_soup_message_body_get_type :: IO GType instance BoxedObject MessageBody where boxedType _ = c_soup_message_body_get_type messageBodyReadData :: MessageBody -> IO T.Text messageBodyReadData s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 0) :: IO CString val' <- cstringToText val return val' messageBodyReadLength :: MessageBody -> IO Int64 messageBodyReadLength s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 8) :: IO Int64 return val -- method MessageBody::new -- method type : Constructor -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TInterface "Soup" "MessageBody" -- throws : False -- Skip return : False foreign import ccall "soup_message_body_new" soup_message_body_new :: IO (Ptr MessageBody) messageBodyNew :: (MonadIO m) => m MessageBody messageBodyNew = liftIO $ do result <- soup_message_body_new checkUnexpectedReturnNULL "soup_message_body_new" result result' <- (wrapBoxed MessageBody) result return result' -- method MessageBody::append_buffer -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer", argType = TInterface "Soup" "Buffer", 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_body_append_buffer" soup_message_body_append_buffer :: Ptr MessageBody -> -- _obj : TInterface "Soup" "MessageBody" Ptr Buffer -> -- buffer : TInterface "Soup" "Buffer" IO () messageBodyAppendBuffer :: (MonadIO m) => MessageBody -> -- _obj Buffer -> -- buffer m () messageBodyAppendBuffer _obj buffer = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj let buffer' = unsafeManagedPtrGetPtr buffer soup_message_body_append_buffer _obj' buffer' touchManagedPtr _obj touchManagedPtr buffer return () -- method MessageBody::append -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_message_body_append_take" soup_message_body_append_take :: Ptr MessageBody -> -- _obj : TInterface "Soup" "MessageBody" Ptr Word8 -> -- data : TCArray False (-1) 2 (TBasicType TUInt8) Word64 -> -- length : TBasicType TUInt64 IO () messageBodyAppend :: (MonadIO m) => MessageBody -> -- _obj ByteString -> -- data m () messageBodyAppend _obj data_ = liftIO $ do let length_ = fromIntegral $ B.length data_ let _obj' = unsafeManagedPtrGetPtr _obj data_' <- packByteString data_ soup_message_body_append_take _obj' data_' length_ touchManagedPtr _obj return () -- method MessageBody::complete -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", 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_body_complete" soup_message_body_complete :: Ptr MessageBody -> -- _obj : TInterface "Soup" "MessageBody" IO () messageBodyComplete :: (MonadIO m) => MessageBody -> -- _obj m () messageBodyComplete _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj soup_message_body_complete _obj' touchManagedPtr _obj return () -- method MessageBody::flatten -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Buffer" -- throws : False -- Skip return : False foreign import ccall "soup_message_body_flatten" soup_message_body_flatten :: Ptr MessageBody -> -- _obj : TInterface "Soup" "MessageBody" IO (Ptr Buffer) messageBodyFlatten :: (MonadIO m) => MessageBody -> -- _obj m Buffer messageBodyFlatten _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_message_body_flatten _obj' checkUnexpectedReturnNULL "soup_message_body_flatten" result result' <- (wrapBoxed Buffer) result touchManagedPtr _obj return result' -- method MessageBody::free -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", 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_body_free" soup_message_body_free :: Ptr MessageBody -> -- _obj : TInterface "Soup" "MessageBody" IO () messageBodyFree :: (MonadIO m) => MessageBody -> -- _obj m () messageBodyFree _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj soup_message_body_free _obj' touchManagedPtr _obj return () -- method MessageBody::get_accumulate -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", 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_body_get_accumulate" soup_message_body_get_accumulate :: Ptr MessageBody -> -- _obj : TInterface "Soup" "MessageBody" IO CInt messageBodyGetAccumulate :: (MonadIO m) => MessageBody -> -- _obj m Bool messageBodyGetAccumulate _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_message_body_get_accumulate _obj' let result' = (/= 0) result touchManagedPtr _obj return result' -- method MessageBody::get_chunk -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "offset", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "offset", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Buffer" -- throws : False -- Skip return : False foreign import ccall "soup_message_body_get_chunk" soup_message_body_get_chunk :: Ptr MessageBody -> -- _obj : TInterface "Soup" "MessageBody" Int64 -> -- offset : TBasicType TInt64 IO (Ptr Buffer) messageBodyGetChunk :: (MonadIO m) => MessageBody -> -- _obj Int64 -> -- offset m Buffer messageBodyGetChunk _obj offset = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_message_body_get_chunk _obj' offset checkUnexpectedReturnNULL "soup_message_body_get_chunk" result result' <- (wrapBoxed Buffer) result touchManagedPtr _obj return result' -- method MessageBody::got_chunk -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "chunk", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "chunk", argType = TInterface "Soup" "Buffer", 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_body_got_chunk" soup_message_body_got_chunk :: Ptr MessageBody -> -- _obj : TInterface "Soup" "MessageBody" Ptr Buffer -> -- chunk : TInterface "Soup" "Buffer" IO () messageBodyGotChunk :: (MonadIO m) => MessageBody -> -- _obj Buffer -> -- chunk m () messageBodyGotChunk _obj chunk = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj let chunk' = unsafeManagedPtrGetPtr chunk soup_message_body_got_chunk _obj' chunk' touchManagedPtr _obj touchManagedPtr chunk return () -- method MessageBody::set_accumulate -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "accumulate", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "accumulate", argType = TBasicType TBoolean, 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_body_set_accumulate" soup_message_body_set_accumulate :: Ptr MessageBody -> -- _obj : TInterface "Soup" "MessageBody" CInt -> -- accumulate : TBasicType TBoolean IO () messageBodySetAccumulate :: (MonadIO m) => MessageBody -> -- _obj Bool -> -- accumulate m () messageBodySetAccumulate _obj accumulate = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj let accumulate' = (fromIntegral . fromEnum) accumulate soup_message_body_set_accumulate _obj' accumulate' touchManagedPtr _obj return () -- method MessageBody::truncate -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", 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_body_truncate" soup_message_body_truncate :: Ptr MessageBody -> -- _obj : TInterface "Soup" "MessageBody" IO () messageBodyTruncate :: (MonadIO m) => MessageBody -> -- _obj m () messageBodyTruncate _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj soup_message_body_truncate _obj' touchManagedPtr _obj return () -- method MessageBody::wrote_chunk -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "chunk", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "chunk", argType = TInterface "Soup" "Buffer", 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_body_wrote_chunk" soup_message_body_wrote_chunk :: Ptr MessageBody -> -- _obj : TInterface "Soup" "MessageBody" Ptr Buffer -> -- chunk : TInterface "Soup" "Buffer" IO () messageBodyWroteChunk :: (MonadIO m) => MessageBody -> -- _obj Buffer -> -- chunk m () messageBodyWroteChunk _obj chunk = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj let chunk' = unsafeManagedPtrGetPtr chunk soup_message_body_wrote_chunk _obj' chunk' touchManagedPtr _obj touchManagedPtr chunk return () -- Flags MessageFlags data MessageFlags = MessageFlagsNoRedirect | MessageFlagsCanRebuild | MessageFlagsOverwriteChunks | MessageFlagsContentDecoded | MessageFlagsCertificateTrusted | MessageFlagsNewConnection | MessageFlagsIdempotent | MessageFlagsIgnoreConnectionLimits | AnotherMessageFlags Int deriving (Show, Eq) instance Enum MessageFlags where fromEnum MessageFlagsNoRedirect = 2 fromEnum MessageFlagsCanRebuild = 4 fromEnum MessageFlagsOverwriteChunks = 8 fromEnum MessageFlagsContentDecoded = 16 fromEnum MessageFlagsCertificateTrusted = 32 fromEnum MessageFlagsNewConnection = 64 fromEnum MessageFlagsIdempotent = 128 fromEnum MessageFlagsIgnoreConnectionLimits = 256 fromEnum (AnotherMessageFlags k) = k toEnum 2 = MessageFlagsNoRedirect toEnum 4 = MessageFlagsCanRebuild toEnum 8 = MessageFlagsOverwriteChunks toEnum 16 = MessageFlagsContentDecoded toEnum 32 = MessageFlagsCertificateTrusted toEnum 64 = MessageFlagsNewConnection toEnum 128 = MessageFlagsIdempotent toEnum 256 = MessageFlagsIgnoreConnectionLimits toEnum k = AnotherMessageFlags k foreign import ccall "soup_message_flags_get_type" c_soup_message_flags_get_type :: IO GType instance BoxedEnum MessageFlags where boxedEnumType _ = c_soup_message_flags_get_type instance IsGFlag MessageFlags -- struct MessageHeaders newtype MessageHeaders = MessageHeaders (ForeignPtr MessageHeaders) noMessageHeaders :: Maybe MessageHeaders noMessageHeaders = Nothing 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 -- 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 () -- callback MessageHeadersForeachFunc messageHeadersForeachFuncClosure :: MessageHeadersForeachFunc -> IO Closure messageHeadersForeachFuncClosure cb = newCClosure =<< mkMessageHeadersForeachFunc wrapped where wrapped = messageHeadersForeachFuncWrapper Nothing cb type MessageHeadersForeachFuncC = CString -> CString -> Ptr () -> IO () foreign import ccall "wrapper" mkMessageHeadersForeachFunc :: MessageHeadersForeachFuncC -> IO (FunPtr MessageHeadersForeachFuncC) type MessageHeadersForeachFunc = T.Text -> T.Text -> IO () noMessageHeadersForeachFunc :: Maybe MessageHeadersForeachFunc noMessageHeadersForeachFunc = Nothing messageHeadersForeachFuncWrapper :: Maybe (Ptr (FunPtr (MessageHeadersForeachFuncC))) -> MessageHeadersForeachFunc -> CString -> CString -> Ptr () -> IO () messageHeadersForeachFuncWrapper funptrptr _cb name value _ = do name' <- cstringToText name value' <- cstringToText value _cb name' value' maybeReleaseFunPtr funptrptr -- struct MessageHeadersIter newtype MessageHeadersIter = MessageHeadersIter (ForeignPtr MessageHeadersIter) noMessageHeadersIter :: Maybe MessageHeadersIter noMessageHeadersIter = Nothing -- method MessageHeadersIter::next -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeadersIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MessageHeadersIter", 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_iter_next" soup_message_headers_iter_next :: Ptr MessageHeadersIter -> -- _obj : TInterface "Soup" "MessageHeadersIter" Ptr CString -> -- name : TBasicType TUTF8 Ptr CString -> -- value : TBasicType TUTF8 IO CInt messageHeadersIterNext :: (MonadIO m) => MessageHeadersIter -> -- _obj m (Bool,T.Text,T.Text) messageHeadersIterNext _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj name <- allocMem :: IO (Ptr CString) value <- allocMem :: IO (Ptr CString) result <- soup_message_headers_iter_next _obj' name value let result' = (/= 0) result name' <- peek name name'' <- cstringToText name' value' <- peek value value'' <- cstringToText value' touchManagedPtr _obj freeMem name freeMem value return (result', name'', value'') -- Enum MessageHeadersType data MessageHeadersType = MessageHeadersTypeRequest | MessageHeadersTypeResponse | MessageHeadersTypeMultipart | AnotherMessageHeadersType Int deriving (Show, Eq) instance Enum MessageHeadersType where fromEnum MessageHeadersTypeRequest = 0 fromEnum MessageHeadersTypeResponse = 1 fromEnum MessageHeadersTypeMultipart = 2 fromEnum (AnotherMessageHeadersType k) = k toEnum 0 = MessageHeadersTypeRequest toEnum 1 = MessageHeadersTypeResponse toEnum 2 = MessageHeadersTypeMultipart toEnum k = AnotherMessageHeadersType k foreign import ccall "soup_message_headers_type_get_type" c_soup_message_headers_type_get_type :: IO GType instance BoxedEnum MessageHeadersType where boxedEnumType _ = c_soup_message_headers_type_get_type -- Enum MessagePriority data MessagePriority = MessagePriorityVeryLow | MessagePriorityLow | MessagePriorityNormal | MessagePriorityHigh | MessagePriorityVeryHigh | AnotherMessagePriority Int deriving (Show, Eq) instance Enum MessagePriority where fromEnum MessagePriorityVeryLow = 0 fromEnum MessagePriorityLow = 1 fromEnum MessagePriorityNormal = 2 fromEnum MessagePriorityHigh = 3 fromEnum MessagePriorityVeryHigh = 4 fromEnum (AnotherMessagePriority k) = k toEnum 0 = MessagePriorityVeryLow toEnum 1 = MessagePriorityLow toEnum 2 = MessagePriorityNormal toEnum 3 = MessagePriorityHigh toEnum 4 = MessagePriorityVeryHigh toEnum k = AnotherMessagePriority k foreign import ccall "soup_message_priority_get_type" c_soup_message_priority_get_type :: IO GType instance BoxedEnum MessagePriority where boxedEnumType _ = c_soup_message_priority_get_type -- struct MessageQueue newtype MessageQueue = MessageQueue (ForeignPtr MessageQueue) noMessageQueue :: Maybe MessageQueue noMessageQueue = Nothing -- struct MessageQueueItem newtype MessageQueueItem = MessageQueueItem (ForeignPtr MessageQueueItem) noMessageQueueItem :: Maybe MessageQueueItem noMessageQueueItem = Nothing -- struct Multipart newtype Multipart = Multipart (ForeignPtr Multipart) noMultipart :: Maybe Multipart noMultipart = Nothing foreign import ccall "soup_multipart_get_type" c_soup_multipart_get_type :: IO GType instance BoxedObject Multipart where boxedType _ = c_soup_multipart_get_type -- method Multipart::new -- method type : Constructor -- Args : [Arg {argName = "mime_type", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "mime_type", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Multipart" -- throws : False -- Skip return : False foreign import ccall "soup_multipart_new" soup_multipart_new :: CString -> -- mime_type : TBasicType TUTF8 IO (Ptr Multipart) multipartNew :: (MonadIO m) => T.Text -> -- mime_type m Multipart multipartNew mime_type = liftIO $ do mime_type' <- textToCString mime_type result <- soup_multipart_new mime_type' checkUnexpectedReturnNULL "soup_multipart_new" result result' <- (wrapBoxed Multipart) result freeMem mime_type' return result' -- method Multipart::new_from_message -- method type : Constructor -- Args : [Arg {argName = "headers", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "body", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "headers", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "body", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Multipart" -- throws : False -- Skip return : False foreign import ccall "soup_multipart_new_from_message" soup_multipart_new_from_message :: Ptr MessageHeaders -> -- headers : TInterface "Soup" "MessageHeaders" Ptr MessageBody -> -- body : TInterface "Soup" "MessageBody" IO (Ptr Multipart) multipartNewFromMessage :: (MonadIO m) => MessageHeaders -> -- headers MessageBody -> -- body m Multipart multipartNewFromMessage headers body = liftIO $ do let headers' = unsafeManagedPtrGetPtr headers let body' = unsafeManagedPtrGetPtr body result <- soup_multipart_new_from_message headers' body' checkUnexpectedReturnNULL "soup_multipart_new_from_message" result result' <- (wrapBoxed Multipart) result touchManagedPtr headers touchManagedPtr body return result' -- method Multipart::append_form_file -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Multipart", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "control_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "filename", argType = TBasicType TUTF8, 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 = "body", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Multipart", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "control_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "filename", argType = TBasicType TUTF8, 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 = "body", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_multipart_append_form_file" soup_multipart_append_form_file :: Ptr Multipart -> -- _obj : TInterface "Soup" "Multipart" CString -> -- control_name : TBasicType TUTF8 CString -> -- filename : TBasicType TUTF8 CString -> -- content_type : TBasicType TUTF8 Ptr Buffer -> -- body : TInterface "Soup" "Buffer" IO () multipartAppendFormFile :: (MonadIO m) => Multipart -> -- _obj T.Text -> -- control_name T.Text -> -- filename T.Text -> -- content_type Buffer -> -- body m () multipartAppendFormFile _obj control_name filename content_type body = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj control_name' <- textToCString control_name filename' <- textToCString filename content_type' <- textToCString content_type let body' = unsafeManagedPtrGetPtr body soup_multipart_append_form_file _obj' control_name' filename' content_type' body' touchManagedPtr _obj touchManagedPtr body freeMem control_name' freeMem filename' freeMem content_type' return () -- method Multipart::append_form_string -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Multipart", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "control_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Multipart", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "control_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", 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_multipart_append_form_string" soup_multipart_append_form_string :: Ptr Multipart -> -- _obj : TInterface "Soup" "Multipart" CString -> -- control_name : TBasicType TUTF8 CString -> -- data : TBasicType TUTF8 IO () multipartAppendFormString :: (MonadIO m) => Multipart -> -- _obj T.Text -> -- control_name T.Text -> -- data m () multipartAppendFormString _obj control_name data_ = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj control_name' <- textToCString control_name data_' <- textToCString data_ soup_multipart_append_form_string _obj' control_name' data_' touchManagedPtr _obj freeMem control_name' freeMem data_' return () -- method Multipart::append_part -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Multipart", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "headers", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "body", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Multipart", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "headers", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "body", argType = TInterface "Soup" "Buffer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_multipart_append_part" soup_multipart_append_part :: Ptr Multipart -> -- _obj : TInterface "Soup" "Multipart" Ptr MessageHeaders -> -- headers : TInterface "Soup" "MessageHeaders" Ptr Buffer -> -- body : TInterface "Soup" "Buffer" IO () multipartAppendPart :: (MonadIO m) => Multipart -> -- _obj MessageHeaders -> -- headers Buffer -> -- body m () multipartAppendPart _obj headers body = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj let headers' = unsafeManagedPtrGetPtr headers let body' = unsafeManagedPtrGetPtr body soup_multipart_append_part _obj' headers' body' touchManagedPtr _obj touchManagedPtr headers touchManagedPtr body return () -- method Multipart::free -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Multipart", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Multipart", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_multipart_free" soup_multipart_free :: Ptr Multipart -> -- _obj : TInterface "Soup" "Multipart" IO () multipartFree :: (MonadIO m) => Multipart -> -- _obj m () multipartFree _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj soup_multipart_free _obj' touchManagedPtr _obj return () -- method Multipart::get_length -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Multipart", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Multipart", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TInt32 -- throws : False -- Skip return : False foreign import ccall "soup_multipart_get_length" soup_multipart_get_length :: Ptr Multipart -> -- _obj : TInterface "Soup" "Multipart" IO Int32 multipartGetLength :: (MonadIO m) => Multipart -> -- _obj m Int32 multipartGetLength _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_multipart_get_length _obj' touchManagedPtr _obj return result -- method Multipart::get_part -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Multipart", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "part", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "headers", argType = TInterface "Soup" "MessageHeaders", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "body", argType = TInterface "Soup" "Buffer", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Multipart", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "part", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_multipart_get_part" soup_multipart_get_part :: Ptr Multipart -> -- _obj : TInterface "Soup" "Multipart" Int32 -> -- part : TBasicType TInt32 Ptr (Ptr MessageHeaders) -> -- headers : TInterface "Soup" "MessageHeaders" Ptr Buffer -> -- body : TInterface "Soup" "Buffer" IO CInt multipartGetPart :: (MonadIO m) => Multipart -> -- _obj Int32 -> -- part m (Bool,MessageHeaders,Buffer) multipartGetPart _obj part = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj headers <- allocMem :: IO (Ptr (Ptr MessageHeaders)) body <- callocBoxedBytes 16 :: IO (Ptr Buffer) result <- soup_multipart_get_part _obj' part headers body let result' = (/= 0) result headers' <- peek headers headers'' <- (newBoxed MessageHeaders) headers' body' <- (wrapBoxed Buffer) body touchManagedPtr _obj freeMem headers return (result', headers'', body') -- method Multipart::to_message -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Multipart", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dest_headers", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dest_body", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Multipart", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dest_headers", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dest_body", argType = TInterface "Soup" "MessageBody", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_multipart_to_message" soup_multipart_to_message :: Ptr Multipart -> -- _obj : TInterface "Soup" "Multipart" Ptr MessageHeaders -> -- dest_headers : TInterface "Soup" "MessageHeaders" Ptr MessageBody -> -- dest_body : TInterface "Soup" "MessageBody" IO () multipartToMessage :: (MonadIO m) => Multipart -> -- _obj MessageHeaders -> -- dest_headers MessageBody -> -- dest_body m () multipartToMessage _obj dest_headers dest_body = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj let dest_headers' = unsafeManagedPtrGetPtr dest_headers let dest_body' = unsafeManagedPtrGetPtr dest_body soup_multipart_to_message _obj' dest_headers' dest_body' touchManagedPtr _obj touchManagedPtr dest_headers touchManagedPtr dest_body return () -- object MultipartInputStream newtype MultipartInputStream = MultipartInputStream (ForeignPtr MultipartInputStream) noMultipartInputStream :: Maybe MultipartInputStream noMultipartInputStream = Nothing foreign import ccall "soup_multipart_input_stream_get_type" c_soup_multipart_input_stream_get_type :: IO GType type instance ParentTypes MultipartInputStream = '[Gio.FilterInputStream, Gio.InputStream, GObject.Object, Gio.PollableInputStream] instance GObject MultipartInputStream where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_multipart_input_stream_get_type class GObject o => MultipartInputStreamK o instance (GObject o, IsDescendantOf MultipartInputStream o) => MultipartInputStreamK o toMultipartInputStream :: MultipartInputStreamK o => o -> IO MultipartInputStream toMultipartInputStream = unsafeCastTo MultipartInputStream -- method MultipartInputStream::new -- method type : Constructor -- Args : [Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "base_stream", argType = TInterface "Gio" "InputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "base_stream", argType = TInterface "Gio" "InputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "MultipartInputStream" -- throws : False -- Skip return : False foreign import ccall "soup_multipart_input_stream_new" soup_multipart_input_stream_new :: Ptr Message -> -- msg : TInterface "Soup" "Message" Ptr Gio.InputStream -> -- base_stream : TInterface "Gio" "InputStream" IO (Ptr MultipartInputStream) multipartInputStreamNew :: (MonadIO m, MessageK a, Gio.InputStreamK b) => a -> -- msg b -> -- base_stream m MultipartInputStream multipartInputStreamNew msg base_stream = liftIO $ do let msg' = unsafeManagedPtrCastPtr msg let base_stream' = unsafeManagedPtrCastPtr base_stream result <- soup_multipart_input_stream_new msg' base_stream' checkUnexpectedReturnNULL "soup_multipart_input_stream_new" result result' <- (wrapObject MultipartInputStream) result touchManagedPtr msg touchManagedPtr base_stream return result' -- method MultipartInputStream::get_headers -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MultipartInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MultipartInputStream", 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_multipart_input_stream_get_headers" soup_multipart_input_stream_get_headers :: Ptr MultipartInputStream -> -- _obj : TInterface "Soup" "MultipartInputStream" IO (Ptr MessageHeaders) multipartInputStreamGetHeaders :: (MonadIO m, MultipartInputStreamK a) => a -> -- _obj m MessageHeaders multipartInputStreamGetHeaders _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_multipart_input_stream_get_headers _obj' checkUnexpectedReturnNULL "soup_multipart_input_stream_get_headers" result result' <- (newBoxed MessageHeaders) result touchManagedPtr _obj return result' -- method MultipartInputStream::next_part -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MultipartInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MultipartInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Gio" "InputStream" -- throws : True -- Skip return : False foreign import ccall "soup_multipart_input_stream_next_part" soup_multipart_input_stream_next_part :: Ptr MultipartInputStream -> -- _obj : TInterface "Soup" "MultipartInputStream" Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" Ptr (Ptr GError) -> -- error IO (Ptr Gio.InputStream) multipartInputStreamNextPart :: (MonadIO m, MultipartInputStreamK a, Gio.CancellableK b) => a -> -- _obj Maybe (b) -> -- cancellable m Gio.InputStream multipartInputStreamNextPart _obj cancellable = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' onException (do result <- propagateGError $ soup_multipart_input_stream_next_part _obj' maybeCancellable checkUnexpectedReturnNULL "soup_multipart_input_stream_next_part" result result' <- (wrapObject Gio.InputStream) result touchManagedPtr _obj whenJust cancellable touchManagedPtr return result' ) (do return () ) -- method MultipartInputStream::next_part_async -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MultipartInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "io_priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 4, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MultipartInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "io_priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 4, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_multipart_input_stream_next_part_async" soup_multipart_input_stream_next_part_async :: Ptr MultipartInputStream -> -- _obj : TInterface "Soup" "MultipartInputStream" Int32 -> -- io_priority : TBasicType TInt32 Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" FunPtr Gio.AsyncReadyCallbackC -> -- callback : TInterface "Gio" "AsyncReadyCallback" Ptr () -> -- data : TBasicType TVoid IO () multipartInputStreamNextPartAsync :: (MonadIO m, MultipartInputStreamK a, Gio.CancellableK b) => a -> -- _obj Int32 -> -- io_priority Maybe (b) -> -- cancellable Maybe (Gio.AsyncReadyCallback) -> -- callback m () multipartInputStreamNextPartAsync _obj io_priority cancellable callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' ptrcallback <- callocMem :: IO (Ptr (FunPtr Gio.AsyncReadyCallbackC)) maybeCallback <- case callback of Nothing -> return (castPtrToFunPtr nullPtr) Just jCallback -> do jCallback' <- Gio.mkAsyncReadyCallback (Gio.asyncReadyCallbackWrapper (Just ptrcallback) jCallback) poke ptrcallback jCallback' return jCallback' let data_ = nullPtr soup_multipart_input_stream_next_part_async _obj' io_priority maybeCancellable maybeCallback data_ touchManagedPtr _obj whenJust cancellable touchManagedPtr return () -- method MultipartInputStream::next_part_finish -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "MultipartInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "MultipartInputStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Gio" "InputStream" -- throws : True -- Skip return : False foreign import ccall "soup_multipart_input_stream_next_part_finish" soup_multipart_input_stream_next_part_finish :: Ptr MultipartInputStream -> -- _obj : TInterface "Soup" "MultipartInputStream" Ptr Gio.AsyncResult -> -- result : TInterface "Gio" "AsyncResult" Ptr (Ptr GError) -> -- error IO (Ptr Gio.InputStream) multipartInputStreamNextPartFinish :: (MonadIO m, MultipartInputStreamK a, Gio.AsyncResultK b) => a -> -- _obj b -> -- result m Gio.InputStream multipartInputStreamNextPartFinish _obj result_ = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let result_' = unsafeManagedPtrCastPtr result_ onException (do result <- propagateGError $ soup_multipart_input_stream_next_part_finish _obj' result_' checkUnexpectedReturnNULL "soup_multipart_input_stream_next_part_finish" result result' <- (wrapObject Gio.InputStream) result touchManagedPtr _obj touchManagedPtr result_ return result' ) (do return () ) -- interface PasswordManager newtype PasswordManager = PasswordManager (ForeignPtr PasswordManager) noPasswordManager :: Maybe PasswordManager noPasswordManager = Nothing foreign import ccall "soup_password_manager_get_type" c_soup_password_manager_get_type :: IO GType type instance ParentTypes PasswordManager = '[SessionFeature, GObject.Object] instance GObject PasswordManager where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_password_manager_get_type class GObject o => PasswordManagerK o instance (GObject o, IsDescendantOf PasswordManager o) => PasswordManagerK o toPasswordManager :: PasswordManagerK o => o -> IO PasswordManager toPasswordManager = unsafeCastTo PasswordManager -- method PasswordManager::get_passwords_async -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "PasswordManager", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "auth", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "retrying", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "async_context", argType = TInterface "GLib" "MainContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "PasswordManagerCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = 7, 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" "PasswordManager", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "auth", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "retrying", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "async_context", argType = TInterface "GLib" "MainContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "PasswordManagerCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = 7, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_password_manager_get_passwords_async" soup_password_manager_get_passwords_async :: Ptr PasswordManager -> -- _obj : TInterface "Soup" "PasswordManager" Ptr Message -> -- msg : TInterface "Soup" "Message" Ptr Auth -> -- auth : TInterface "Soup" "Auth" CInt -> -- retrying : TBasicType TBoolean Ptr GLib.MainContext -> -- async_context : TInterface "GLib" "MainContext" Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" FunPtr PasswordManagerCallbackC -> -- callback : TInterface "Soup" "PasswordManagerCallback" Ptr () -> -- user_data : TBasicType TVoid IO () passwordManagerGetPasswordsAsync :: (MonadIO m, PasswordManagerK a, MessageK b, AuthK c, Gio.CancellableK d) => a -> -- _obj b -> -- msg c -> -- auth Bool -> -- retrying GLib.MainContext -> -- async_context Maybe (d) -> -- cancellable PasswordManagerCallback -> -- callback m () passwordManagerGetPasswordsAsync _obj msg auth retrying async_context cancellable callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg let auth' = unsafeManagedPtrCastPtr auth let retrying' = (fromIntegral . fromEnum) retrying let async_context' = unsafeManagedPtrGetPtr async_context maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' ptrcallback <- callocMem :: IO (Ptr (FunPtr PasswordManagerCallbackC)) callback' <- mkPasswordManagerCallback (passwordManagerCallbackWrapper (Just ptrcallback) callback) poke ptrcallback callback' let user_data = nullPtr soup_password_manager_get_passwords_async _obj' msg' auth' retrying' async_context' maybeCancellable callback' user_data touchManagedPtr _obj touchManagedPtr msg touchManagedPtr auth touchManagedPtr async_context whenJust cancellable touchManagedPtr return () -- method PasswordManager::get_passwords_sync -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "PasswordManager", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "auth", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "PasswordManager", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "auth", argType = TInterface "Soup" "Auth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_password_manager_get_passwords_sync" soup_password_manager_get_passwords_sync :: Ptr PasswordManager -> -- _obj : TInterface "Soup" "PasswordManager" Ptr Message -> -- msg : TInterface "Soup" "Message" Ptr Auth -> -- auth : TInterface "Soup" "Auth" Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" IO () passwordManagerGetPasswordsSync :: (MonadIO m, PasswordManagerK a, MessageK b, AuthK c, Gio.CancellableK d) => a -> -- _obj b -> -- msg c -> -- auth Maybe (d) -> -- cancellable m () passwordManagerGetPasswordsSync _obj msg auth cancellable = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg let auth' = unsafeManagedPtrCastPtr auth maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' soup_password_manager_get_passwords_sync _obj' msg' auth' maybeCancellable touchManagedPtr _obj touchManagedPtr msg touchManagedPtr auth whenJust cancellable touchManagedPtr return () -- callback PasswordManagerCallback passwordManagerCallbackClosure :: PasswordManagerCallback -> IO Closure passwordManagerCallbackClosure cb = newCClosure =<< mkPasswordManagerCallback wrapped where wrapped = passwordManagerCallbackWrapper Nothing cb type PasswordManagerCallbackC = Ptr PasswordManager -> Ptr Message -> Ptr Auth -> CInt -> Ptr () -> IO () foreign import ccall "wrapper" mkPasswordManagerCallback :: PasswordManagerCallbackC -> IO (FunPtr PasswordManagerCallbackC) type PasswordManagerCallback = PasswordManager -> Message -> Auth -> Bool -> IO () noPasswordManagerCallback :: Maybe PasswordManagerCallback noPasswordManagerCallback = Nothing passwordManagerCallbackWrapper :: Maybe (Ptr (FunPtr (PasswordManagerCallbackC))) -> PasswordManagerCallback -> Ptr PasswordManager -> Ptr Message -> Ptr Auth -> CInt -> Ptr () -> IO () passwordManagerCallbackWrapper funptrptr _cb password_manager msg auth retrying _ = do password_manager' <- (newObject PasswordManager) password_manager msg' <- (newObject Message) msg auth' <- (newObject Auth) auth let retrying' = (/= 0) retrying _cb password_manager' msg' auth' retrying' maybeReleaseFunPtr funptrptr -- object ProxyResolverDefault newtype ProxyResolverDefault = ProxyResolverDefault (ForeignPtr ProxyResolverDefault) noProxyResolverDefault :: Maybe ProxyResolverDefault noProxyResolverDefault = Nothing foreign import ccall "soup_proxy_resolver_default_get_type" c_soup_proxy_resolver_default_get_type :: IO GType type instance ParentTypes ProxyResolverDefault = '[GObject.Object, ProxyURIResolver, SessionFeature] instance GObject ProxyResolverDefault where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_proxy_resolver_default_get_type class GObject o => ProxyResolverDefaultK o instance (GObject o, IsDescendantOf ProxyResolverDefault o) => ProxyResolverDefaultK o toProxyResolverDefault :: ProxyResolverDefaultK o => o -> IO ProxyResolverDefault toProxyResolverDefault = unsafeCastTo ProxyResolverDefault -- interface ProxyURIResolver newtype ProxyURIResolver = ProxyURIResolver (ForeignPtr ProxyURIResolver) noProxyURIResolver :: Maybe ProxyURIResolver noProxyURIResolver = Nothing foreign import ccall "soup_proxy_uri_resolver_get_type" c_soup_proxy_uri_resolver_get_type :: IO GType type instance ParentTypes ProxyURIResolver = '[SessionFeature, GObject.Object] instance GObject ProxyURIResolver where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_proxy_uri_resolver_get_type class GObject o => ProxyURIResolverK o instance (GObject o, IsDescendantOf ProxyURIResolver o) => ProxyURIResolverK o toProxyURIResolver :: ProxyURIResolverK o => o -> IO ProxyURIResolver toProxyURIResolver = unsafeCastTo ProxyURIResolver -- method ProxyURIResolver::get_proxy_uri_async -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "ProxyURIResolver", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "async_context", argType = TInterface "GLib" "MainContext", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "ProxyURIResolverCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = 5, 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" "ProxyURIResolver", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "async_context", argType = TInterface "GLib" "MainContext", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "ProxyURIResolverCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = 5, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_proxy_uri_resolver_get_proxy_uri_async" soup_proxy_uri_resolver_get_proxy_uri_async :: Ptr ProxyURIResolver -> -- _obj : TInterface "Soup" "ProxyURIResolver" Ptr URI -> -- uri : TInterface "Soup" "URI" Ptr GLib.MainContext -> -- async_context : TInterface "GLib" "MainContext" Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" FunPtr ProxyURIResolverCallbackC -> -- callback : TInterface "Soup" "ProxyURIResolverCallback" Ptr () -> -- user_data : TBasicType TVoid IO () {-# DEPRECATED proxyURIResolverGetProxyUriAsync ["#SoupProxyURIResolver is deprecated in favor of","#GProxyResolver"]#-} proxyURIResolverGetProxyUriAsync :: (MonadIO m, ProxyURIResolverK a, Gio.CancellableK b) => a -> -- _obj URI -> -- uri Maybe (GLib.MainContext) -> -- async_context Maybe (b) -> -- cancellable ProxyURIResolverCallback -> -- callback m () proxyURIResolverGetProxyUriAsync _obj uri async_context cancellable callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let uri' = unsafeManagedPtrGetPtr uri maybeAsync_context <- case async_context of Nothing -> return nullPtr Just jAsync_context -> do let jAsync_context' = unsafeManagedPtrGetPtr jAsync_context return jAsync_context' maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' ptrcallback <- callocMem :: IO (Ptr (FunPtr ProxyURIResolverCallbackC)) callback' <- mkProxyURIResolverCallback (proxyURIResolverCallbackWrapper (Just ptrcallback) callback) poke ptrcallback callback' let user_data = nullPtr soup_proxy_uri_resolver_get_proxy_uri_async _obj' uri' maybeAsync_context maybeCancellable callback' user_data touchManagedPtr _obj touchManagedPtr uri whenJust async_context touchManagedPtr whenJust cancellable touchManagedPtr return () -- method ProxyURIResolver::get_proxy_uri_sync -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "ProxyURIResolver", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "proxy_uri", argType = TInterface "Soup" "URI", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "ProxyURIResolver", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_proxy_uri_resolver_get_proxy_uri_sync" soup_proxy_uri_resolver_get_proxy_uri_sync :: Ptr ProxyURIResolver -> -- _obj : TInterface "Soup" "ProxyURIResolver" Ptr URI -> -- uri : TInterface "Soup" "URI" Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" Ptr URI -> -- proxy_uri : TInterface "Soup" "URI" IO Word32 {-# DEPRECATED proxyURIResolverGetProxyUriSync ["#SoupProxyURIResolver is deprecated in favor of","#GProxyResolver"]#-} proxyURIResolverGetProxyUriSync :: (MonadIO m, ProxyURIResolverK a, Gio.CancellableK b) => a -> -- _obj URI -> -- uri Maybe (b) -> -- cancellable m (Word32,URI) proxyURIResolverGetProxyUriSync _obj uri cancellable = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let uri' = unsafeManagedPtrGetPtr uri maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' proxy_uri <- callocBoxedBytes 64 :: IO (Ptr URI) result <- soup_proxy_uri_resolver_get_proxy_uri_sync _obj' uri' maybeCancellable proxy_uri proxy_uri' <- (wrapBoxed URI) proxy_uri touchManagedPtr _obj touchManagedPtr uri whenJust cancellable touchManagedPtr return (result, proxy_uri') -- callback ProxyURIResolverCallback proxyURIResolverCallbackClosure :: ProxyURIResolverCallback -> IO Closure proxyURIResolverCallbackClosure cb = newCClosure =<< mkProxyURIResolverCallback wrapped where wrapped = proxyURIResolverCallbackWrapper Nothing cb type ProxyURIResolverCallbackC = Ptr ProxyURIResolver -> Word32 -> Ptr URI -> Ptr () -> IO () foreign import ccall "wrapper" mkProxyURIResolverCallback :: ProxyURIResolverCallbackC -> IO (FunPtr ProxyURIResolverCallbackC) type ProxyURIResolverCallback = ProxyURIResolver -> Word32 -> URI -> IO () noProxyURIResolverCallback :: Maybe ProxyURIResolverCallback noProxyURIResolverCallback = Nothing proxyURIResolverCallbackWrapper :: Maybe (Ptr (FunPtr (ProxyURIResolverCallbackC))) -> ProxyURIResolverCallback -> Ptr ProxyURIResolver -> Word32 -> Ptr URI -> Ptr () -> IO () proxyURIResolverCallbackWrapper funptrptr _cb resolver status proxy_uri _ = do resolver' <- (newObject ProxyURIResolver) resolver proxy_uri' <- (newBoxed URI) proxy_uri _cb resolver' status proxy_uri' maybeReleaseFunPtr funptrptr -- struct Range newtype Range = Range (ForeignPtr Range) noRange :: Maybe Range noRange = Nothing rangeReadStart :: Range -> IO Int64 rangeReadStart s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 0) :: IO Int64 return val rangeReadEnd :: Range -> IO Int64 rangeReadEnd s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 8) :: IO Int64 return val -- object Request newtype Request = Request (ForeignPtr Request) noRequest :: Maybe Request noRequest = Nothing foreign import ccall "soup_request_get_type" c_soup_request_get_type :: IO GType type instance ParentTypes Request = '[GObject.Object, Gio.Initable] instance GObject Request where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_request_get_type class GObject o => RequestK o instance (GObject o, IsDescendantOf Request o) => RequestK o toRequest :: RequestK o => o -> IO Request toRequest = unsafeCastTo Request -- method Request::get_content_length -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Request", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Request", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TInt64 -- throws : False -- Skip return : False foreign import ccall "soup_request_get_content_length" soup_request_get_content_length :: Ptr Request -> -- _obj : TInterface "Soup" "Request" IO Int64 requestGetContentLength :: (MonadIO m, RequestK a) => a -> -- _obj m Int64 requestGetContentLength _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_request_get_content_length _obj' touchManagedPtr _obj return result -- method Request::get_content_type -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Request", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Request", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_request_get_content_type" soup_request_get_content_type :: Ptr Request -> -- _obj : TInterface "Soup" "Request" IO CString requestGetContentType :: (MonadIO m, RequestK a) => a -> -- _obj m T.Text requestGetContentType _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_request_get_content_type _obj' checkUnexpectedReturnNULL "soup_request_get_content_type" result result' <- cstringToText result touchManagedPtr _obj return result' -- method Request::get_session -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Request", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Request", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Session" -- throws : False -- Skip return : False foreign import ccall "soup_request_get_session" soup_request_get_session :: Ptr Request -> -- _obj : TInterface "Soup" "Request" IO (Ptr Session) requestGetSession :: (MonadIO m, RequestK a) => a -> -- _obj m Session requestGetSession _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_request_get_session _obj' checkUnexpectedReturnNULL "soup_request_get_session" result result' <- (newObject Session) result touchManagedPtr _obj return result' -- method Request::get_uri -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Request", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Request", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "URI" -- throws : False -- Skip return : False foreign import ccall "soup_request_get_uri" soup_request_get_uri :: Ptr Request -> -- _obj : TInterface "Soup" "Request" IO (Ptr URI) requestGetUri :: (MonadIO m, RequestK a) => a -> -- _obj m URI requestGetUri _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_request_get_uri _obj' checkUnexpectedReturnNULL "soup_request_get_uri" result result' <- (newBoxed URI) result touchManagedPtr _obj return result' -- method Request::send -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Request", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Request", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Gio" "InputStream" -- throws : True -- Skip return : False foreign import ccall "soup_request_send" soup_request_send :: Ptr Request -> -- _obj : TInterface "Soup" "Request" Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" Ptr (Ptr GError) -> -- error IO (Ptr Gio.InputStream) requestSend :: (MonadIO m, RequestK a, Gio.CancellableK b) => a -> -- _obj Maybe (b) -> -- cancellable m Gio.InputStream requestSend _obj cancellable = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' onException (do result <- propagateGError $ soup_request_send _obj' maybeCancellable checkUnexpectedReturnNULL "soup_request_send" result result' <- (wrapObject Gio.InputStream) result touchManagedPtr _obj whenJust cancellable touchManagedPtr return result' ) (do return () ) -- method Request::send_async -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Request", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 3, 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" "Request", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 3, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_request_send_async" soup_request_send_async :: Ptr Request -> -- _obj : TInterface "Soup" "Request" Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" FunPtr Gio.AsyncReadyCallbackC -> -- callback : TInterface "Gio" "AsyncReadyCallback" Ptr () -> -- user_data : TBasicType TVoid IO () requestSendAsync :: (MonadIO m, RequestK a, Gio.CancellableK b) => a -> -- _obj Maybe (b) -> -- cancellable Maybe (Gio.AsyncReadyCallback) -> -- callback m () requestSendAsync _obj cancellable callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' ptrcallback <- callocMem :: IO (Ptr (FunPtr Gio.AsyncReadyCallbackC)) maybeCallback <- case callback of Nothing -> return (castPtrToFunPtr nullPtr) Just jCallback -> do jCallback' <- Gio.mkAsyncReadyCallback (Gio.asyncReadyCallbackWrapper (Just ptrcallback) jCallback) poke ptrcallback jCallback' return jCallback' let user_data = nullPtr soup_request_send_async _obj' maybeCancellable maybeCallback user_data touchManagedPtr _obj whenJust cancellable touchManagedPtr return () -- method Request::send_finish -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Request", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Request", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Gio" "InputStream" -- throws : True -- Skip return : False foreign import ccall "soup_request_send_finish" soup_request_send_finish :: Ptr Request -> -- _obj : TInterface "Soup" "Request" Ptr Gio.AsyncResult -> -- result : TInterface "Gio" "AsyncResult" Ptr (Ptr GError) -> -- error IO (Ptr Gio.InputStream) requestSendFinish :: (MonadIO m, RequestK a, Gio.AsyncResultK b) => a -> -- _obj b -> -- result m Gio.InputStream requestSendFinish _obj result_ = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let result_' = unsafeManagedPtrCastPtr result_ onException (do result <- propagateGError $ soup_request_send_finish _obj' result_' checkUnexpectedReturnNULL "soup_request_send_finish" result result' <- (wrapObject Gio.InputStream) result touchManagedPtr _obj touchManagedPtr result_ return result' ) (do return () ) -- object RequestData newtype RequestData = RequestData (ForeignPtr RequestData) noRequestData :: Maybe RequestData noRequestData = Nothing foreign import ccall "soup_request_data_get_type" c_soup_request_data_get_type :: IO GType type instance ParentTypes RequestData = '[Request, GObject.Object, Gio.Initable] instance GObject RequestData where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_request_data_get_type class GObject o => RequestDataK o instance (GObject o, IsDescendantOf RequestData o) => RequestDataK o toRequestData :: RequestDataK o => o -> IO RequestData toRequestData = unsafeCastTo RequestData -- Enum RequestError data RequestError = RequestErrorBadUri | RequestErrorUnsupportedUriScheme | RequestErrorParsing | RequestErrorEncoding | AnotherRequestError Int deriving (Show, Eq) instance Enum RequestError where fromEnum RequestErrorBadUri = 0 fromEnum RequestErrorUnsupportedUriScheme = 1 fromEnum RequestErrorParsing = 2 fromEnum RequestErrorEncoding = 3 fromEnum (AnotherRequestError k) = k toEnum 0 = RequestErrorBadUri toEnum 1 = RequestErrorUnsupportedUriScheme toEnum 2 = RequestErrorParsing toEnum 3 = RequestErrorEncoding toEnum k = AnotherRequestError k instance GErrorClass RequestError where gerrorClassDomain _ = "soup_request_error_quark" catchRequestError :: IO a -> (RequestError -> GErrorMessage -> IO a) -> IO a catchRequestError = catchGErrorJustDomain handleRequestError :: (RequestError -> GErrorMessage -> IO a) -> IO a -> IO a handleRequestError = handleGErrorJustDomain foreign import ccall "soup_request_error_get_type" c_soup_request_error_get_type :: IO GType instance BoxedEnum RequestError where boxedEnumType _ = c_soup_request_error_get_type -- object RequestFile newtype RequestFile = RequestFile (ForeignPtr RequestFile) noRequestFile :: Maybe RequestFile noRequestFile = Nothing foreign import ccall "soup_request_file_get_type" c_soup_request_file_get_type :: IO GType type instance ParentTypes RequestFile = '[Request, GObject.Object, Gio.Initable] instance GObject RequestFile where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_request_file_get_type class GObject o => RequestFileK o instance (GObject o, IsDescendantOf RequestFile o) => RequestFileK o toRequestFile :: RequestFileK o => o -> IO RequestFile toRequestFile = unsafeCastTo RequestFile -- method RequestFile::get_file -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "RequestFile", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "RequestFile", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Gio" "File" -- throws : False -- Skip return : False foreign import ccall "soup_request_file_get_file" soup_request_file_get_file :: Ptr RequestFile -> -- _obj : TInterface "Soup" "RequestFile" IO (Ptr Gio.File) requestFileGetFile :: (MonadIO m, RequestFileK a) => a -> -- _obj m Gio.File requestFileGetFile _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_request_file_get_file _obj' checkUnexpectedReturnNULL "soup_request_file_get_file" result result' <- (wrapObject Gio.File) result touchManagedPtr _obj return result' -- object RequestHTTP newtype RequestHTTP = RequestHTTP (ForeignPtr RequestHTTP) noRequestHTTP :: Maybe RequestHTTP noRequestHTTP = Nothing foreign import ccall "soup_request_http_get_type" c_soup_request_http_get_type :: IO GType type instance ParentTypes RequestHTTP = '[Request, GObject.Object, Gio.Initable] instance GObject RequestHTTP where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_request_http_get_type class GObject o => RequestHTTPK o instance (GObject o, IsDescendantOf RequestHTTP o) => RequestHTTPK o toRequestHTTP :: RequestHTTPK o => o -> IO RequestHTTP toRequestHTTP = unsafeCastTo RequestHTTP -- method RequestHTTP::get_message -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "RequestHTTP", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "RequestHTTP", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Message" -- throws : False -- Skip return : False foreign import ccall "soup_request_http_get_message" soup_request_http_get_message :: Ptr RequestHTTP -> -- _obj : TInterface "Soup" "RequestHTTP" IO (Ptr Message) requestHTTPGetMessage :: (MonadIO m, RequestHTTPK a) => a -> -- _obj m Message requestHTTPGetMessage _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_request_http_get_message _obj' checkUnexpectedReturnNULL "soup_request_http_get_message" result result' <- (wrapObject Message) result touchManagedPtr _obj return result' -- object Requester newtype Requester = Requester (ForeignPtr Requester) noRequester :: Maybe Requester noRequester = Nothing foreign import ccall "soup_requester_get_type" c_soup_requester_get_type :: IO GType type instance ParentTypes Requester = '[GObject.Object, SessionFeature] instance GObject Requester where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_requester_get_type class GObject o => RequesterK o instance (GObject o, IsDescendantOf Requester o) => RequesterK o toRequester :: RequesterK o => o -> IO Requester toRequester = unsafeCastTo Requester -- method Requester::new -- method type : Constructor -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TInterface "Soup" "Requester" -- throws : False -- Skip return : False foreign import ccall "soup_requester_new" soup_requester_new :: IO (Ptr Requester) requesterNew :: (MonadIO m) => m Requester requesterNew = liftIO $ do result <- soup_requester_new checkUnexpectedReturnNULL "soup_requester_new" result result' <- (wrapObject Requester) result return result' -- method Requester::request -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Requester", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Requester", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Request" -- throws : True -- Skip return : False foreign import ccall "soup_requester_request" soup_requester_request :: Ptr Requester -> -- _obj : TInterface "Soup" "Requester" CString -> -- uri_string : TBasicType TUTF8 Ptr (Ptr GError) -> -- error IO (Ptr Request) requesterRequest :: (MonadIO m, RequesterK a) => a -> -- _obj T.Text -> -- uri_string m Request requesterRequest _obj uri_string = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj uri_string' <- textToCString uri_string onException (do result <- propagateGError $ soup_requester_request _obj' uri_string' checkUnexpectedReturnNULL "soup_requester_request" result result' <- (wrapObject Request) result touchManagedPtr _obj freeMem uri_string' return result' ) (do freeMem uri_string' ) -- method Requester::request_uri -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Requester", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Requester", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Request" -- throws : True -- Skip return : False foreign import ccall "soup_requester_request_uri" soup_requester_request_uri :: Ptr Requester -> -- _obj : TInterface "Soup" "Requester" Ptr URI -> -- uri : TInterface "Soup" "URI" Ptr (Ptr GError) -> -- error IO (Ptr Request) requesterRequestUri :: (MonadIO m, RequesterK a) => a -> -- _obj URI -> -- uri m Request requesterRequestUri _obj uri = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let uri' = unsafeManagedPtrGetPtr uri onException (do result <- propagateGError $ soup_requester_request_uri _obj' uri' checkUnexpectedReturnNULL "soup_requester_request_uri" result result' <- (wrapObject Request) result touchManagedPtr _obj touchManagedPtr uri return result' ) (do return () ) -- Enum RequesterError data RequesterError = RequesterErrorBadUri | RequesterErrorUnsupportedUriScheme | AnotherRequesterError Int deriving (Show, Eq) instance Enum RequesterError where fromEnum RequesterErrorBadUri = 0 fromEnum RequesterErrorUnsupportedUriScheme = 1 fromEnum (AnotherRequesterError k) = k toEnum 0 = RequesterErrorBadUri toEnum 1 = RequesterErrorUnsupportedUriScheme toEnum k = AnotherRequesterError k instance GErrorClass RequesterError where gerrorClassDomain _ = "soup_requester_error_quark" catchRequesterError :: IO a -> (RequesterError -> GErrorMessage -> IO a) -> IO a catchRequesterError = catchGErrorJustDomain handleRequesterError :: (RequesterError -> GErrorMessage -> IO a) -> IO a -> IO a handleRequesterError = handleGErrorJustDomain foreign import ccall "soup_requester_error_get_type" c_soup_requester_error_get_type :: IO GType instance BoxedEnum RequesterError where boxedEnumType _ = c_soup_requester_error_get_type -- object Server newtype Server = Server (ForeignPtr Server) noServer :: Maybe Server noServer = Nothing foreign import ccall "soup_server_get_type" c_soup_server_get_type :: IO GType type instance ParentTypes Server = '[GObject.Object] instance GObject Server where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_server_get_type class GObject o => ServerK o instance (GObject o, IsDescendantOf Server o) => ServerK o toServer :: ServerK o => o -> IO Server toServer = unsafeCastTo Server -- method Server::accept_iostream -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stream", argType = TInterface "Gio" "IOStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "local_addr", argType = TInterface "Gio" "SocketAddress", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "remote_addr", argType = TInterface "Gio" "SocketAddress", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stream", argType = TInterface "Gio" "IOStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "local_addr", argType = TInterface "Gio" "SocketAddress", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "remote_addr", argType = TInterface "Gio" "SocketAddress", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : True -- Skip return : False foreign import ccall "soup_server_accept_iostream" soup_server_accept_iostream :: Ptr Server -> -- _obj : TInterface "Soup" "Server" Ptr Gio.IOStream -> -- stream : TInterface "Gio" "IOStream" Ptr Gio.SocketAddress -> -- local_addr : TInterface "Gio" "SocketAddress" Ptr Gio.SocketAddress -> -- remote_addr : TInterface "Gio" "SocketAddress" Ptr (Ptr GError) -> -- error IO CInt serverAcceptIostream :: (MonadIO m, ServerK a, Gio.IOStreamK b, Gio.SocketAddressK c, Gio.SocketAddressK d) => a -> -- _obj b -> -- stream Maybe (c) -> -- local_addr Maybe (d) -> -- remote_addr m () serverAcceptIostream _obj stream local_addr remote_addr = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let stream' = unsafeManagedPtrCastPtr stream maybeLocal_addr <- case local_addr of Nothing -> return nullPtr Just jLocal_addr -> do let jLocal_addr' = unsafeManagedPtrCastPtr jLocal_addr return jLocal_addr' maybeRemote_addr <- case remote_addr of Nothing -> return nullPtr Just jRemote_addr -> do let jRemote_addr' = unsafeManagedPtrCastPtr jRemote_addr return jRemote_addr' onException (do _ <- propagateGError $ soup_server_accept_iostream _obj' stream' maybeLocal_addr maybeRemote_addr touchManagedPtr _obj touchManagedPtr stream whenJust local_addr touchManagedPtr whenJust remote_addr touchManagedPtr return () ) (do return () ) -- method Server::add_auth_domain -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "auth_domain", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "auth_domain", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_server_add_auth_domain" soup_server_add_auth_domain :: Ptr Server -> -- _obj : TInterface "Soup" "Server" Ptr AuthDomain -> -- auth_domain : TInterface "Soup" "AuthDomain" IO () serverAddAuthDomain :: (MonadIO m, ServerK a, AuthDomainK b) => a -> -- _obj b -> -- auth_domain m () serverAddAuthDomain _obj auth_domain = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let auth_domain' = unsafeManagedPtrCastPtr auth_domain soup_server_add_auth_domain _obj' auth_domain' touchManagedPtr _obj touchManagedPtr auth_domain return () -- method Server::add_early_handler -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "ServerCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 3, argDestroy = 4, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "destroy", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "ServerCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 3, argDestroy = 4, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_server_add_early_handler" soup_server_add_early_handler :: Ptr Server -> -- _obj : TInterface "Soup" "Server" CString -> -- path : TBasicType TUTF8 FunPtr ServerCallbackC -> -- callback : TInterface "Soup" "ServerCallback" Ptr () -> -- user_data : TBasicType TVoid FunPtr GLib.DestroyNotifyC -> -- destroy : TInterface "GLib" "DestroyNotify" IO () serverAddEarlyHandler :: (MonadIO m, ServerK a) => a -> -- _obj Maybe (T.Text) -> -- path ServerCallback -> -- callback m () serverAddEarlyHandler _obj path callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj maybePath <- case path of Nothing -> return nullPtr Just jPath -> do jPath' <- textToCString jPath return jPath' callback' <- mkServerCallback (serverCallbackWrapper Nothing callback) let user_data = castFunPtrToPtr callback' let destroy = safeFreeFunPtrPtr soup_server_add_early_handler _obj' maybePath callback' user_data destroy touchManagedPtr _obj freeMem maybePath return () -- method Server::add_handler -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "ServerCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 3, argDestroy = 4, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "destroy", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "ServerCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 3, argDestroy = 4, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_server_add_handler" soup_server_add_handler :: Ptr Server -> -- _obj : TInterface "Soup" "Server" CString -> -- path : TBasicType TUTF8 FunPtr ServerCallbackC -> -- callback : TInterface "Soup" "ServerCallback" Ptr () -> -- user_data : TBasicType TVoid FunPtr GLib.DestroyNotifyC -> -- destroy : TInterface "GLib" "DestroyNotify" IO () serverAddHandler :: (MonadIO m, ServerK a) => a -> -- _obj Maybe (T.Text) -> -- path ServerCallback -> -- callback m () serverAddHandler _obj path callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj maybePath <- case path of Nothing -> return nullPtr Just jPath -> do jPath' <- textToCString jPath return jPath' callback' <- mkServerCallback (serverCallbackWrapper Nothing callback) let user_data = castFunPtrToPtr callback' let destroy = safeFreeFunPtrPtr soup_server_add_handler _obj' maybePath callback' user_data destroy touchManagedPtr _obj freeMem maybePath return () -- method Server::add_websocket_handler -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "origin", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "protocols", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "ServerWebsocketCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 5, argDestroy = 6, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "destroy", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "origin", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "protocols", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "ServerWebsocketCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 5, argDestroy = 6, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_server_add_websocket_handler" soup_server_add_websocket_handler :: Ptr Server -> -- _obj : TInterface "Soup" "Server" CString -> -- path : TBasicType TUTF8 CString -> -- origin : TBasicType TUTF8 Ptr CString -> -- protocols : TCArray True (-1) (-1) (TBasicType TUTF8) FunPtr ServerWebsocketCallbackC -> -- callback : TInterface "Soup" "ServerWebsocketCallback" Ptr () -> -- user_data : TBasicType TVoid FunPtr GLib.DestroyNotifyC -> -- destroy : TInterface "GLib" "DestroyNotify" IO () serverAddWebsocketHandler :: (MonadIO m, ServerK a) => a -> -- _obj Maybe (T.Text) -> -- path Maybe (T.Text) -> -- origin Maybe ([T.Text]) -> -- protocols ServerWebsocketCallback -> -- callback m () serverAddWebsocketHandler _obj path origin protocols callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj maybePath <- case path of Nothing -> return nullPtr Just jPath -> do jPath' <- textToCString jPath return jPath' maybeOrigin <- case origin of Nothing -> return nullPtr Just jOrigin -> do jOrigin' <- textToCString jOrigin return jOrigin' maybeProtocols <- case protocols of Nothing -> return nullPtr Just jProtocols -> do jProtocols' <- packZeroTerminatedUTF8CArray jProtocols return jProtocols' callback' <- mkServerWebsocketCallback (serverWebsocketCallbackWrapper Nothing callback) let user_data = castFunPtrToPtr callback' let destroy = safeFreeFunPtrPtr soup_server_add_websocket_handler _obj' maybePath maybeOrigin maybeProtocols callback' user_data destroy touchManagedPtr _obj freeMem maybePath freeMem maybeOrigin mapZeroTerminatedCArray freeMem maybeProtocols freeMem maybeProtocols return () -- method Server::disconnect -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_server_disconnect" soup_server_disconnect :: Ptr Server -> -- _obj : TInterface "Soup" "Server" IO () serverDisconnect :: (MonadIO m, ServerK a) => a -> -- _obj m () serverDisconnect _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_server_disconnect _obj' touchManagedPtr _obj return () -- method Server::get_async_context -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "GLib" "MainContext" -- throws : False -- Skip return : False foreign import ccall "soup_server_get_async_context" soup_server_get_async_context :: Ptr Server -> -- _obj : TInterface "Soup" "Server" IO (Ptr GLib.MainContext) {-# DEPRECATED serverGetAsyncContext ["If you are using soup_server_listen(), etc, then","the server listens on the thread-default #GMainContext, and this","property is ignored."]#-} serverGetAsyncContext :: (MonadIO m, ServerK a) => a -> -- _obj m GLib.MainContext serverGetAsyncContext _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_server_get_async_context _obj' checkUnexpectedReturnNULL "soup_server_get_async_context" result result' <- (newBoxed GLib.MainContext) result touchManagedPtr _obj return result' -- method Server::get_listener -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Socket" -- throws : False -- Skip return : False foreign import ccall "soup_server_get_listener" soup_server_get_listener :: Ptr Server -> -- _obj : TInterface "Soup" "Server" IO (Ptr Socket) {-# DEPRECATED serverGetListener ["If you are using soup_server_listen(), etc, then use","soup_server_get_listeners() to get a list of all listening sockets,","but note that that function returns #GSockets, not #SoupSockets."]#-} serverGetListener :: (MonadIO m, ServerK a) => a -> -- _obj m Socket serverGetListener _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_server_get_listener _obj' checkUnexpectedReturnNULL "soup_server_get_listener" result result' <- (newObject Socket) result touchManagedPtr _obj return result' -- method Server::get_listeners -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TGSList (TInterface "Gio" "Socket") -- throws : False -- Skip return : False foreign import ccall "soup_server_get_listeners" soup_server_get_listeners :: Ptr Server -> -- _obj : TInterface "Soup" "Server" IO (Ptr (GSList (Ptr Gio.Socket))) serverGetListeners :: (MonadIO m, ServerK a) => a -> -- _obj m [Gio.Socket] serverGetListeners _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_server_get_listeners _obj' checkUnexpectedReturnNULL "soup_server_get_listeners" result result' <- unpackGSList result result'' <- mapM (newObject Gio.Socket) result' g_slist_free result touchManagedPtr _obj return result'' -- method Server::get_port -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_server_get_port" soup_server_get_port :: Ptr Server -> -- _obj : TInterface "Soup" "Server" IO Word32 {-# DEPRECATED serverGetPort ["If you are using soup_server_listen(), etc, then use","soup_server_get_uris() to get a list of all listening addresses."]#-} serverGetPort :: (MonadIO m, ServerK a) => a -> -- _obj m Word32 serverGetPort _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_server_get_port _obj' touchManagedPtr _obj return result -- method Server::get_uris -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TGSList (TInterface "Soup" "URI") -- throws : False -- Skip return : False foreign import ccall "soup_server_get_uris" soup_server_get_uris :: Ptr Server -> -- _obj : TInterface "Soup" "Server" IO (Ptr (GSList (Ptr URI))) serverGetUris :: (MonadIO m, ServerK a) => a -> -- _obj m [URI] serverGetUris _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_server_get_uris _obj' checkUnexpectedReturnNULL "soup_server_get_uris" result result' <- unpackGSList result result'' <- mapM (wrapBoxed URI) result' g_slist_free result touchManagedPtr _obj return result'' -- method Server::is_https -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_server_is_https" soup_server_is_https :: Ptr Server -> -- _obj : TInterface "Soup" "Server" IO CInt serverIsHttps :: (MonadIO m, ServerK a) => a -> -- _obj m Bool serverIsHttps _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_server_is_https _obj' let result' = (/= 0) result touchManagedPtr _obj return result' -- method Server::listen -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "address", argType = TInterface "Gio" "SocketAddress", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "options", argType = TInterface "Soup" "ServerListenOptions", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "address", argType = TInterface "Gio" "SocketAddress", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "options", argType = TInterface "Soup" "ServerListenOptions", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : True -- Skip return : False foreign import ccall "soup_server_listen" soup_server_listen :: Ptr Server -> -- _obj : TInterface "Soup" "Server" Ptr Gio.SocketAddress -> -- address : TInterface "Gio" "SocketAddress" CUInt -> -- options : TInterface "Soup" "ServerListenOptions" Ptr (Ptr GError) -> -- error IO CInt serverListen :: (MonadIO m, ServerK a, Gio.SocketAddressK b) => a -> -- _obj b -> -- address [ServerListenOptions] -> -- options m () serverListen _obj address options = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let address' = unsafeManagedPtrCastPtr address let options' = gflagsToWord options onException (do _ <- propagateGError $ soup_server_listen _obj' address' options' touchManagedPtr _obj touchManagedPtr address return () ) (do return () ) -- method Server::listen_all -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "port", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "options", argType = TInterface "Soup" "ServerListenOptions", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "port", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "options", argType = TInterface "Soup" "ServerListenOptions", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : True -- Skip return : False foreign import ccall "soup_server_listen_all" soup_server_listen_all :: Ptr Server -> -- _obj : TInterface "Soup" "Server" Word32 -> -- port : TBasicType TUInt32 CUInt -> -- options : TInterface "Soup" "ServerListenOptions" Ptr (Ptr GError) -> -- error IO CInt serverListenAll :: (MonadIO m, ServerK a) => a -> -- _obj Word32 -> -- port [ServerListenOptions] -> -- options m () serverListenAll _obj port options = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let options' = gflagsToWord options onException (do _ <- propagateGError $ soup_server_listen_all _obj' port options' touchManagedPtr _obj return () ) (do return () ) -- method Server::listen_fd -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "fd", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "options", argType = TInterface "Soup" "ServerListenOptions", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "fd", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "options", argType = TInterface "Soup" "ServerListenOptions", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : True -- Skip return : False foreign import ccall "soup_server_listen_fd" soup_server_listen_fd :: Ptr Server -> -- _obj : TInterface "Soup" "Server" Int32 -> -- fd : TBasicType TInt32 CUInt -> -- options : TInterface "Soup" "ServerListenOptions" Ptr (Ptr GError) -> -- error IO CInt serverListenFd :: (MonadIO m, ServerK a) => a -> -- _obj Int32 -> -- fd [ServerListenOptions] -> -- options m () serverListenFd _obj fd options = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let options' = gflagsToWord options onException (do _ <- propagateGError $ soup_server_listen_fd _obj' fd options' touchManagedPtr _obj return () ) (do return () ) -- method Server::listen_local -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "port", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "options", argType = TInterface "Soup" "ServerListenOptions", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "port", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "options", argType = TInterface "Soup" "ServerListenOptions", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : True -- Skip return : False foreign import ccall "soup_server_listen_local" soup_server_listen_local :: Ptr Server -> -- _obj : TInterface "Soup" "Server" Word32 -> -- port : TBasicType TUInt32 CUInt -> -- options : TInterface "Soup" "ServerListenOptions" Ptr (Ptr GError) -> -- error IO CInt serverListenLocal :: (MonadIO m, ServerK a) => a -> -- _obj Word32 -> -- port [ServerListenOptions] -> -- options m () serverListenLocal _obj port options = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let options' = gflagsToWord options onException (do _ <- propagateGError $ soup_server_listen_local _obj' port options' touchManagedPtr _obj return () ) (do return () ) -- method Server::listen_socket -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "socket", argType = TInterface "Gio" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "options", argType = TInterface "Soup" "ServerListenOptions", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "socket", argType = TInterface "Gio" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "options", argType = TInterface "Soup" "ServerListenOptions", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : True -- Skip return : False foreign import ccall "soup_server_listen_socket" soup_server_listen_socket :: Ptr Server -> -- _obj : TInterface "Soup" "Server" Ptr Gio.Socket -> -- socket : TInterface "Gio" "Socket" CUInt -> -- options : TInterface "Soup" "ServerListenOptions" Ptr (Ptr GError) -> -- error IO CInt serverListenSocket :: (MonadIO m, ServerK a, Gio.SocketK b) => a -> -- _obj b -> -- socket [ServerListenOptions] -> -- options m () serverListenSocket _obj socket options = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let socket' = unsafeManagedPtrCastPtr socket let options' = gflagsToWord options onException (do _ <- propagateGError $ soup_server_listen_socket _obj' socket' options' touchManagedPtr _obj touchManagedPtr socket return () ) (do return () ) -- method Server::pause_message -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_server_pause_message" soup_server_pause_message :: Ptr Server -> -- _obj : TInterface "Soup" "Server" Ptr Message -> -- msg : TInterface "Soup" "Message" IO () serverPauseMessage :: (MonadIO m, ServerK a, MessageK b) => a -> -- _obj b -> -- msg m () serverPauseMessage _obj msg = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg soup_server_pause_message _obj' msg' touchManagedPtr _obj touchManagedPtr msg return () -- method Server::quit -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_server_quit" soup_server_quit :: Ptr Server -> -- _obj : TInterface "Soup" "Server" IO () {-# DEPRECATED serverQuit ["When using soup_server_listen(), etc, the server will","always listen for connections, and will process them whenever the","thread-default #GMainContext is running."]#-} serverQuit :: (MonadIO m, ServerK a) => a -> -- _obj m () serverQuit _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_server_quit _obj' touchManagedPtr _obj return () -- method Server::remove_auth_domain -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "auth_domain", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "auth_domain", argType = TInterface "Soup" "AuthDomain", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_server_remove_auth_domain" soup_server_remove_auth_domain :: Ptr Server -> -- _obj : TInterface "Soup" "Server" Ptr AuthDomain -> -- auth_domain : TInterface "Soup" "AuthDomain" IO () serverRemoveAuthDomain :: (MonadIO m, ServerK a, AuthDomainK b) => a -> -- _obj b -> -- auth_domain m () serverRemoveAuthDomain _obj auth_domain = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let auth_domain' = unsafeManagedPtrCastPtr auth_domain soup_server_remove_auth_domain _obj' auth_domain' touchManagedPtr _obj touchManagedPtr auth_domain return () -- method Server::remove_handler -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", 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_server_remove_handler" soup_server_remove_handler :: Ptr Server -> -- _obj : TInterface "Soup" "Server" CString -> -- path : TBasicType TUTF8 IO () serverRemoveHandler :: (MonadIO m, ServerK a) => a -> -- _obj T.Text -> -- path m () serverRemoveHandler _obj path = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj path' <- textToCString path soup_server_remove_handler _obj' path' touchManagedPtr _obj freeMem path' return () -- method Server::run -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_server_run" soup_server_run :: Ptr Server -> -- _obj : TInterface "Soup" "Server" IO () {-# DEPRECATED serverRun ["When using soup_server_listen(), etc, the server will","always listen for connections, and will process them whenever the","thread-default #GMainContext is running."]#-} serverRun :: (MonadIO m, ServerK a) => a -> -- _obj m () serverRun _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_server_run _obj' touchManagedPtr _obj return () -- method Server::run_async -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_server_run_async" soup_server_run_async :: Ptr Server -> -- _obj : TInterface "Soup" "Server" IO () {-# DEPRECATED serverRunAsync ["When using soup_server_listen(), etc, the server will","always listen for connections, and will process them whenever the","thread-default #GMainContext is running."]#-} serverRunAsync :: (MonadIO m, ServerK a) => a -> -- _obj m () serverRunAsync _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_server_run_async _obj' touchManagedPtr _obj return () -- method Server::set_ssl_cert_file -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ssl_cert_file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ssl_key_file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ssl_cert_file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ssl_key_file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : True -- Skip return : False foreign import ccall "soup_server_set_ssl_cert_file" soup_server_set_ssl_cert_file :: Ptr Server -> -- _obj : TInterface "Soup" "Server" CString -> -- ssl_cert_file : TBasicType TUTF8 CString -> -- ssl_key_file : TBasicType TUTF8 Ptr (Ptr GError) -> -- error IO CInt serverSetSslCertFile :: (MonadIO m, ServerK a) => a -> -- _obj T.Text -> -- ssl_cert_file T.Text -> -- ssl_key_file m () serverSetSslCertFile _obj ssl_cert_file ssl_key_file = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj ssl_cert_file' <- textToCString ssl_cert_file ssl_key_file' <- textToCString ssl_key_file onException (do _ <- propagateGError $ soup_server_set_ssl_cert_file _obj' ssl_cert_file' ssl_key_file' touchManagedPtr _obj freeMem ssl_cert_file' freeMem ssl_key_file' return () ) (do freeMem ssl_cert_file' freeMem ssl_key_file' ) -- method Server::unpause_message -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Server", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_server_unpause_message" soup_server_unpause_message :: Ptr Server -> -- _obj : TInterface "Soup" "Server" Ptr Message -> -- msg : TInterface "Soup" "Message" IO () serverUnpauseMessage :: (MonadIO m, ServerK a, MessageK b) => a -> -- _obj b -> -- msg m () serverUnpauseMessage _obj msg = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg soup_server_unpause_message _obj' msg' touchManagedPtr _obj touchManagedPtr msg return () -- signal Server::request-aborted type ServerRequestAbortedCallback = Message -> ClientContext -> IO () noServerRequestAbortedCallback :: Maybe ServerRequestAbortedCallback noServerRequestAbortedCallback = Nothing type ServerRequestAbortedCallbackC = Ptr () -> -- object Ptr Message -> Ptr ClientContext -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkServerRequestAbortedCallback :: ServerRequestAbortedCallbackC -> IO (FunPtr ServerRequestAbortedCallbackC) serverRequestAbortedClosure :: ServerRequestAbortedCallback -> IO Closure serverRequestAbortedClosure cb = newCClosure =<< mkServerRequestAbortedCallback wrapped where wrapped = serverRequestAbortedCallbackWrapper cb serverRequestAbortedCallbackWrapper :: ServerRequestAbortedCallback -> Ptr () -> Ptr Message -> Ptr ClientContext -> Ptr () -> IO () serverRequestAbortedCallbackWrapper _cb _ message client _ = do message' <- (newObject Message) message client' <- (newBoxed ClientContext) client _cb message' client' onServerRequestAborted :: (GObject a, MonadIO m) => a -> ServerRequestAbortedCallback -> m SignalHandlerId onServerRequestAborted obj cb = liftIO $ connectServerRequestAborted obj cb SignalConnectBefore afterServerRequestAborted :: (GObject a, MonadIO m) => a -> ServerRequestAbortedCallback -> m SignalHandlerId afterServerRequestAborted obj cb = connectServerRequestAborted obj cb SignalConnectAfter connectServerRequestAborted :: (GObject a, MonadIO m) => a -> ServerRequestAbortedCallback -> SignalConnectMode -> m SignalHandlerId connectServerRequestAborted obj cb after = liftIO $ do cb' <- mkServerRequestAbortedCallback (serverRequestAbortedCallbackWrapper cb) connectSignalFunPtr obj "request-aborted" cb' after -- signal Server::request-finished type ServerRequestFinishedCallback = Message -> ClientContext -> IO () noServerRequestFinishedCallback :: Maybe ServerRequestFinishedCallback noServerRequestFinishedCallback = Nothing type ServerRequestFinishedCallbackC = Ptr () -> -- object Ptr Message -> Ptr ClientContext -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkServerRequestFinishedCallback :: ServerRequestFinishedCallbackC -> IO (FunPtr ServerRequestFinishedCallbackC) serverRequestFinishedClosure :: ServerRequestFinishedCallback -> IO Closure serverRequestFinishedClosure cb = newCClosure =<< mkServerRequestFinishedCallback wrapped where wrapped = serverRequestFinishedCallbackWrapper cb serverRequestFinishedCallbackWrapper :: ServerRequestFinishedCallback -> Ptr () -> Ptr Message -> Ptr ClientContext -> Ptr () -> IO () serverRequestFinishedCallbackWrapper _cb _ message client _ = do message' <- (newObject Message) message client' <- (newBoxed ClientContext) client _cb message' client' onServerRequestFinished :: (GObject a, MonadIO m) => a -> ServerRequestFinishedCallback -> m SignalHandlerId onServerRequestFinished obj cb = liftIO $ connectServerRequestFinished obj cb SignalConnectBefore afterServerRequestFinished :: (GObject a, MonadIO m) => a -> ServerRequestFinishedCallback -> m SignalHandlerId afterServerRequestFinished obj cb = connectServerRequestFinished obj cb SignalConnectAfter connectServerRequestFinished :: (GObject a, MonadIO m) => a -> ServerRequestFinishedCallback -> SignalConnectMode -> m SignalHandlerId connectServerRequestFinished obj cb after = liftIO $ do cb' <- mkServerRequestFinishedCallback (serverRequestFinishedCallbackWrapper cb) connectSignalFunPtr obj "request-finished" cb' after -- signal Server::request-read type ServerRequestReadCallback = Message -> ClientContext -> IO () noServerRequestReadCallback :: Maybe ServerRequestReadCallback noServerRequestReadCallback = Nothing type ServerRequestReadCallbackC = Ptr () -> -- object Ptr Message -> Ptr ClientContext -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkServerRequestReadCallback :: ServerRequestReadCallbackC -> IO (FunPtr ServerRequestReadCallbackC) serverRequestReadClosure :: ServerRequestReadCallback -> IO Closure serverRequestReadClosure cb = newCClosure =<< mkServerRequestReadCallback wrapped where wrapped = serverRequestReadCallbackWrapper cb serverRequestReadCallbackWrapper :: ServerRequestReadCallback -> Ptr () -> Ptr Message -> Ptr ClientContext -> Ptr () -> IO () serverRequestReadCallbackWrapper _cb _ message client _ = do message' <- (newObject Message) message client' <- (newBoxed ClientContext) client _cb message' client' onServerRequestRead :: (GObject a, MonadIO m) => a -> ServerRequestReadCallback -> m SignalHandlerId onServerRequestRead obj cb = liftIO $ connectServerRequestRead obj cb SignalConnectBefore afterServerRequestRead :: (GObject a, MonadIO m) => a -> ServerRequestReadCallback -> m SignalHandlerId afterServerRequestRead obj cb = connectServerRequestRead obj cb SignalConnectAfter connectServerRequestRead :: (GObject a, MonadIO m) => a -> ServerRequestReadCallback -> SignalConnectMode -> m SignalHandlerId connectServerRequestRead obj cb after = liftIO $ do cb' <- mkServerRequestReadCallback (serverRequestReadCallbackWrapper cb) connectSignalFunPtr obj "request-read" cb' after -- signal Server::request-started type ServerRequestStartedCallback = Message -> ClientContext -> IO () noServerRequestStartedCallback :: Maybe ServerRequestStartedCallback noServerRequestStartedCallback = Nothing type ServerRequestStartedCallbackC = Ptr () -> -- object Ptr Message -> Ptr ClientContext -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkServerRequestStartedCallback :: ServerRequestStartedCallbackC -> IO (FunPtr ServerRequestStartedCallbackC) serverRequestStartedClosure :: ServerRequestStartedCallback -> IO Closure serverRequestStartedClosure cb = newCClosure =<< mkServerRequestStartedCallback wrapped where wrapped = serverRequestStartedCallbackWrapper cb serverRequestStartedCallbackWrapper :: ServerRequestStartedCallback -> Ptr () -> Ptr Message -> Ptr ClientContext -> Ptr () -> IO () serverRequestStartedCallbackWrapper _cb _ message client _ = do message' <- (newObject Message) message client' <- (newBoxed ClientContext) client _cb message' client' onServerRequestStarted :: (GObject a, MonadIO m) => a -> ServerRequestStartedCallback -> m SignalHandlerId onServerRequestStarted obj cb = liftIO $ connectServerRequestStarted obj cb SignalConnectBefore afterServerRequestStarted :: (GObject a, MonadIO m) => a -> ServerRequestStartedCallback -> m SignalHandlerId afterServerRequestStarted obj cb = connectServerRequestStarted obj cb SignalConnectAfter connectServerRequestStarted :: (GObject a, MonadIO m) => a -> ServerRequestStartedCallback -> SignalConnectMode -> m SignalHandlerId connectServerRequestStarted obj cb after = liftIO $ do cb' <- mkServerRequestStartedCallback (serverRequestStartedCallbackWrapper cb) connectSignalFunPtr obj "request-started" cb' after -- callback ServerCallback serverCallbackClosure :: ServerCallback -> IO Closure serverCallbackClosure cb = newCClosure =<< mkServerCallback wrapped where wrapped = serverCallbackWrapper Nothing cb type ServerCallbackC = Ptr Server -> Ptr Message -> CString -> Ptr (GHashTable CString CString) -> Ptr ClientContext -> Ptr () -> IO () foreign import ccall "wrapper" mkServerCallback :: ServerCallbackC -> IO (FunPtr ServerCallbackC) type ServerCallback = Server -> Message -> T.Text -> Maybe (Map.Map T.Text T.Text) -> ClientContext -> IO () noServerCallback :: Maybe ServerCallback noServerCallback = Nothing serverCallbackWrapper :: Maybe (Ptr (FunPtr (ServerCallbackC))) -> ServerCallback -> Ptr Server -> Ptr Message -> CString -> Ptr (GHashTable CString CString) -> Ptr ClientContext -> Ptr () -> IO () serverCallbackWrapper funptrptr _cb server msg path query client _ = do server' <- (newObject Server) server msg' <- (newObject Message) msg path' <- cstringToText path maybeQuery <- if query == nullPtr then return Nothing else do query' <- unpackGHashTable query let query'' = mapFirst cstringUnpackPtr query' query''' <- mapFirstA cstringToText query'' let query'''' = mapSecond cstringUnpackPtr query''' query''''' <- mapSecondA cstringToText query'''' let query'''''' = Map.fromList query''''' return $ Just query'''''' client' <- (newBoxed ClientContext) client _cb server' msg' path' maybeQuery client' maybeReleaseFunPtr funptrptr -- Flags ServerListenOptions data ServerListenOptions = ServerListenOptionsHttps | ServerListenOptionsIpv4Only | ServerListenOptionsIpv6Only | AnotherServerListenOptions Int deriving (Show, Eq) instance Enum ServerListenOptions where fromEnum ServerListenOptionsHttps = 1 fromEnum ServerListenOptionsIpv4Only = 2 fromEnum ServerListenOptionsIpv6Only = 4 fromEnum (AnotherServerListenOptions k) = k toEnum 1 = ServerListenOptionsHttps toEnum 2 = ServerListenOptionsIpv4Only toEnum 4 = ServerListenOptionsIpv6Only toEnum k = AnotherServerListenOptions k foreign import ccall "soup_server_listen_options_get_type" c_soup_server_listen_options_get_type :: IO GType instance BoxedEnum ServerListenOptions where boxedEnumType _ = c_soup_server_listen_options_get_type instance IsGFlag ServerListenOptions -- callback ServerWebsocketCallback serverWebsocketCallbackClosure :: ServerWebsocketCallback -> IO Closure serverWebsocketCallbackClosure cb = newCClosure =<< mkServerWebsocketCallback wrapped where wrapped = serverWebsocketCallbackWrapper Nothing cb type ServerWebsocketCallbackC = Ptr Server -> Ptr WebsocketConnection -> CString -> Ptr ClientContext -> Ptr () -> IO () foreign import ccall "wrapper" mkServerWebsocketCallback :: ServerWebsocketCallbackC -> IO (FunPtr ServerWebsocketCallbackC) type ServerWebsocketCallback = Server -> WebsocketConnection -> T.Text -> ClientContext -> IO () noServerWebsocketCallback :: Maybe ServerWebsocketCallback noServerWebsocketCallback = Nothing serverWebsocketCallbackWrapper :: Maybe (Ptr (FunPtr (ServerWebsocketCallbackC))) -> ServerWebsocketCallback -> Ptr Server -> Ptr WebsocketConnection -> CString -> Ptr ClientContext -> Ptr () -> IO () serverWebsocketCallbackWrapper funptrptr _cb server connection path client _ = do server' <- (newObject Server) server connection' <- (newObject WebsocketConnection) connection path' <- cstringToText path client' <- (newBoxed ClientContext) client _cb server' connection' path' client' maybeReleaseFunPtr funptrptr -- object Session newtype Session = Session (ForeignPtr Session) noSession :: Maybe Session noSession = Nothing foreign import ccall "soup_session_get_type" c_soup_session_get_type :: IO GType type instance ParentTypes Session = '[GObject.Object] instance GObject Session where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_session_get_type class GObject o => SessionK o instance (GObject o, IsDescendantOf Session o) => SessionK o toSession :: SessionK o => o -> IO Session toSession = unsafeCastTo Session -- method Session::new -- method type : Constructor -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TInterface "Soup" "Session" -- throws : False -- Skip return : False foreign import ccall "soup_session_new" soup_session_new :: IO (Ptr Session) sessionNew :: (MonadIO m) => m Session sessionNew = liftIO $ do result <- soup_session_new checkUnexpectedReturnNULL "soup_session_new" result result' <- (wrapObject Session) result return result' -- method Session::abort -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_session_abort" soup_session_abort :: Ptr Session -> -- _obj : TInterface "Soup" "Session" IO () sessionAbort :: (MonadIO m, SessionK a) => a -> -- _obj m () sessionAbort _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_session_abort _obj' touchManagedPtr _obj return () -- method Session::add_feature -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature", argType = TInterface "Soup" "SessionFeature", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature", argType = TInterface "Soup" "SessionFeature", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_session_add_feature" soup_session_add_feature :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr SessionFeature -> -- feature : TInterface "Soup" "SessionFeature" IO () sessionAddFeature :: (MonadIO m, SessionK a, SessionFeatureK b) => a -> -- _obj b -> -- feature m () sessionAddFeature _obj feature = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let feature' = unsafeManagedPtrCastPtr feature soup_session_add_feature _obj' feature' touchManagedPtr _obj touchManagedPtr feature return () -- method Session::add_feature_by_type -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature_type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature_type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_session_add_feature_by_type" soup_session_add_feature_by_type :: Ptr Session -> -- _obj : TInterface "Soup" "Session" CGType -> -- feature_type : TBasicType TGType IO () sessionAddFeatureByType :: (MonadIO m, SessionK a) => a -> -- _obj GType -> -- feature_type m () sessionAddFeatureByType _obj feature_type = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let feature_type' = gtypeToCGType feature_type soup_session_add_feature_by_type _obj' feature_type' touchManagedPtr _obj return () -- method Session::cancel_message -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "status_code", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "status_code", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_session_cancel_message" soup_session_cancel_message :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr Message -> -- msg : TInterface "Soup" "Message" Word32 -> -- status_code : TBasicType TUInt32 IO () sessionCancelMessage :: (MonadIO m, SessionK a, MessageK b) => a -> -- _obj b -> -- msg Word32 -> -- status_code m () sessionCancelMessage _obj msg status_code = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg soup_session_cancel_message _obj' msg' status_code touchManagedPtr _obj touchManagedPtr msg return () -- method Session::get_async_context -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "GLib" "MainContext" -- throws : False -- Skip return : False foreign import ccall "soup_session_get_async_context" soup_session_get_async_context :: Ptr Session -> -- _obj : TInterface "Soup" "Session" IO (Ptr GLib.MainContext) sessionGetAsyncContext :: (MonadIO m, SessionK a) => a -> -- _obj m GLib.MainContext sessionGetAsyncContext _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_session_get_async_context _obj' checkUnexpectedReturnNULL "soup_session_get_async_context" result result' <- (newBoxed GLib.MainContext) result touchManagedPtr _obj return result' -- method Session::get_feature -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature_type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature_type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "SessionFeature" -- throws : False -- Skip return : False foreign import ccall "soup_session_get_feature" soup_session_get_feature :: Ptr Session -> -- _obj : TInterface "Soup" "Session" CGType -> -- feature_type : TBasicType TGType IO (Ptr SessionFeature) sessionGetFeature :: (MonadIO m, SessionK a) => a -> -- _obj GType -> -- feature_type m SessionFeature sessionGetFeature _obj feature_type = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let feature_type' = gtypeToCGType feature_type result <- soup_session_get_feature _obj' feature_type' checkUnexpectedReturnNULL "soup_session_get_feature" result result' <- (newObject SessionFeature) result touchManagedPtr _obj return result' -- method Session::get_feature_for_message -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature_type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature_type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "SessionFeature" -- throws : False -- Skip return : False foreign import ccall "soup_session_get_feature_for_message" soup_session_get_feature_for_message :: Ptr Session -> -- _obj : TInterface "Soup" "Session" CGType -> -- feature_type : TBasicType TGType Ptr Message -> -- msg : TInterface "Soup" "Message" IO (Ptr SessionFeature) sessionGetFeatureForMessage :: (MonadIO m, SessionK a, MessageK b) => a -> -- _obj GType -> -- feature_type b -> -- msg m SessionFeature sessionGetFeatureForMessage _obj feature_type msg = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let feature_type' = gtypeToCGType feature_type let msg' = unsafeManagedPtrCastPtr msg result <- soup_session_get_feature_for_message _obj' feature_type' msg' checkUnexpectedReturnNULL "soup_session_get_feature_for_message" result result' <- (newObject SessionFeature) result touchManagedPtr _obj touchManagedPtr msg return result' -- method Session::get_features -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature_type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature_type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TGSList (TInterface "Soup" "SessionFeature") -- throws : False -- Skip return : False foreign import ccall "soup_session_get_features" soup_session_get_features :: Ptr Session -> -- _obj : TInterface "Soup" "Session" CGType -> -- feature_type : TBasicType TGType IO (Ptr (GSList (Ptr SessionFeature))) sessionGetFeatures :: (MonadIO m, SessionK a) => a -> -- _obj GType -> -- feature_type m [SessionFeature] sessionGetFeatures _obj feature_type = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let feature_type' = gtypeToCGType feature_type result <- soup_session_get_features _obj' feature_type' checkUnexpectedReturnNULL "soup_session_get_features" result result' <- unpackGSList result result'' <- mapM (newObject SessionFeature) result' g_slist_free result touchManagedPtr _obj return result'' -- method Session::has_feature -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature_type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature_type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_session_has_feature" soup_session_has_feature :: Ptr Session -> -- _obj : TInterface "Soup" "Session" CGType -> -- feature_type : TBasicType TGType IO CInt sessionHasFeature :: (MonadIO m, SessionK a) => a -> -- _obj GType -> -- feature_type m Bool sessionHasFeature _obj feature_type = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let feature_type' = gtypeToCGType feature_type result <- soup_session_has_feature _obj' feature_type' let result' = (/= 0) result touchManagedPtr _obj return result' -- method Session::pause_message -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_session_pause_message" soup_session_pause_message :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr Message -> -- msg : TInterface "Soup" "Message" IO () sessionPauseMessage :: (MonadIO m, SessionK a, MessageK b) => a -> -- _obj b -> -- msg m () sessionPauseMessage _obj msg = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg soup_session_pause_message _obj' msg' touchManagedPtr _obj touchManagedPtr msg return () -- method Session::prefetch_dns -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "AddressCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 4, 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" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "AddressCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 4, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_session_prefetch_dns" soup_session_prefetch_dns :: Ptr Session -> -- _obj : TInterface "Soup" "Session" CString -> -- hostname : TBasicType TUTF8 Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" FunPtr AddressCallbackC -> -- callback : TInterface "Soup" "AddressCallback" Ptr () -> -- user_data : TBasicType TVoid IO () sessionPrefetchDns :: (MonadIO m, SessionK a, Gio.CancellableK b) => a -> -- _obj T.Text -> -- hostname Maybe (b) -> -- cancellable Maybe (AddressCallback) -> -- callback m () sessionPrefetchDns _obj hostname cancellable callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj hostname' <- textToCString hostname maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' ptrcallback <- callocMem :: IO (Ptr (FunPtr AddressCallbackC)) maybeCallback <- case callback of Nothing -> return (castPtrToFunPtr nullPtr) Just jCallback -> do jCallback' <- mkAddressCallback (addressCallbackWrapper (Just ptrcallback) jCallback) poke ptrcallback jCallback' return jCallback' let user_data = nullPtr soup_session_prefetch_dns _obj' hostname' maybeCancellable maybeCallback user_data touchManagedPtr _obj whenJust cancellable touchManagedPtr freeMem hostname' return () -- method Session::prepare_for_uri -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_session_prepare_for_uri" soup_session_prepare_for_uri :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr URI -> -- uri : TInterface "Soup" "URI" IO () {-# DEPRECATED sessionPrepareForUri ["(Since version 2.38)","use soup_session_prefetch_dns() instead"]#-} sessionPrepareForUri :: (MonadIO m, SessionK a) => a -> -- _obj URI -> -- uri m () sessionPrepareForUri _obj uri = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let uri' = unsafeManagedPtrGetPtr uri soup_session_prepare_for_uri _obj' uri' touchManagedPtr _obj touchManagedPtr uri return () -- method Session::queue_message -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "callback", argType = TInterface "Soup" "SessionCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 3, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "callback", argType = TInterface "Soup" "SessionCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 3, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_session_queue_message" soup_session_queue_message :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr Message -> -- msg : TInterface "Soup" "Message" FunPtr SessionCallbackC -> -- callback : TInterface "Soup" "SessionCallback" Ptr () -> -- user_data : TBasicType TVoid IO () sessionQueueMessage :: (MonadIO m, SessionK a, MessageK b) => a -> -- _obj b -> -- msg Maybe (SessionCallback) -> -- callback m () sessionQueueMessage _obj msg callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj msg' <- refObject msg ptrcallback <- callocMem :: IO (Ptr (FunPtr SessionCallbackC)) maybeCallback <- case callback of Nothing -> return (castPtrToFunPtr nullPtr) Just jCallback -> do jCallback' <- mkSessionCallback (sessionCallbackWrapper (Just ptrcallback) jCallback) poke ptrcallback jCallback' return jCallback' let user_data = nullPtr soup_session_queue_message _obj' msg' maybeCallback user_data touchManagedPtr _obj touchManagedPtr msg return () -- method Session::redirect_message -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_session_redirect_message" soup_session_redirect_message :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr Message -> -- msg : TInterface "Soup" "Message" IO CInt sessionRedirectMessage :: (MonadIO m, SessionK a, MessageK b) => a -> -- _obj b -> -- msg m Bool sessionRedirectMessage _obj msg = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg result <- soup_session_redirect_message _obj' msg' let result' = (/= 0) result touchManagedPtr _obj touchManagedPtr msg return result' -- method Session::remove_feature -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature", argType = TInterface "Soup" "SessionFeature", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature", argType = TInterface "Soup" "SessionFeature", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_session_remove_feature" soup_session_remove_feature :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr SessionFeature -> -- feature : TInterface "Soup" "SessionFeature" IO () sessionRemoveFeature :: (MonadIO m, SessionK a, SessionFeatureK b) => a -> -- _obj b -> -- feature m () sessionRemoveFeature _obj feature = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let feature' = unsafeManagedPtrCastPtr feature soup_session_remove_feature _obj' feature' touchManagedPtr _obj touchManagedPtr feature return () -- method Session::remove_feature_by_type -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature_type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "feature_type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_session_remove_feature_by_type" soup_session_remove_feature_by_type :: Ptr Session -> -- _obj : TInterface "Soup" "Session" CGType -> -- feature_type : TBasicType TGType IO () sessionRemoveFeatureByType :: (MonadIO m, SessionK a) => a -> -- _obj GType -> -- feature_type m () sessionRemoveFeatureByType _obj feature_type = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let feature_type' = gtypeToCGType feature_type soup_session_remove_feature_by_type _obj' feature_type' touchManagedPtr _obj return () -- method Session::request -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Request" -- throws : True -- Skip return : False foreign import ccall "soup_session_request" soup_session_request :: Ptr Session -> -- _obj : TInterface "Soup" "Session" CString -> -- uri_string : TBasicType TUTF8 Ptr (Ptr GError) -> -- error IO (Ptr Request) sessionRequest :: (MonadIO m, SessionK a) => a -> -- _obj T.Text -> -- uri_string m Request sessionRequest _obj uri_string = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj uri_string' <- textToCString uri_string onException (do result <- propagateGError $ soup_session_request _obj' uri_string' checkUnexpectedReturnNULL "soup_session_request" result result' <- (wrapObject Request) result touchManagedPtr _obj freeMem uri_string' return result' ) (do freeMem uri_string' ) -- method Session::request_http -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "method", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "method", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "RequestHTTP" -- throws : True -- Skip return : False foreign import ccall "soup_session_request_http" soup_session_request_http :: Ptr Session -> -- _obj : TInterface "Soup" "Session" CString -> -- method : TBasicType TUTF8 CString -> -- uri_string : TBasicType TUTF8 Ptr (Ptr GError) -> -- error IO (Ptr RequestHTTP) sessionRequestHttp :: (MonadIO m, SessionK a) => a -> -- _obj T.Text -> -- method T.Text -> -- uri_string m RequestHTTP sessionRequestHttp _obj method uri_string = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj method' <- textToCString method uri_string' <- textToCString uri_string onException (do result <- propagateGError $ soup_session_request_http _obj' method' uri_string' checkUnexpectedReturnNULL "soup_session_request_http" result result' <- (wrapObject RequestHTTP) result touchManagedPtr _obj freeMem method' freeMem uri_string' return result' ) (do freeMem method' freeMem uri_string' ) -- method Session::request_http_uri -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "method", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "method", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "RequestHTTP" -- throws : True -- Skip return : False foreign import ccall "soup_session_request_http_uri" soup_session_request_http_uri :: Ptr Session -> -- _obj : TInterface "Soup" "Session" CString -> -- method : TBasicType TUTF8 Ptr URI -> -- uri : TInterface "Soup" "URI" Ptr (Ptr GError) -> -- error IO (Ptr RequestHTTP) sessionRequestHttpUri :: (MonadIO m, SessionK a) => a -> -- _obj T.Text -> -- method URI -> -- uri m RequestHTTP sessionRequestHttpUri _obj method uri = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj method' <- textToCString method let uri' = unsafeManagedPtrGetPtr uri onException (do result <- propagateGError $ soup_session_request_http_uri _obj' method' uri' checkUnexpectedReturnNULL "soup_session_request_http_uri" result result' <- (wrapObject RequestHTTP) result touchManagedPtr _obj touchManagedPtr uri freeMem method' return result' ) (do freeMem method' ) -- method Session::request_uri -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Request" -- throws : True -- Skip return : False foreign import ccall "soup_session_request_uri" soup_session_request_uri :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr URI -> -- uri : TInterface "Soup" "URI" Ptr (Ptr GError) -> -- error IO (Ptr Request) sessionRequestUri :: (MonadIO m, SessionK a) => a -> -- _obj URI -> -- uri m Request sessionRequestUri _obj uri = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let uri' = unsafeManagedPtrGetPtr uri onException (do result <- propagateGError $ soup_session_request_uri _obj' uri' checkUnexpectedReturnNULL "soup_session_request_uri" result result' <- (wrapObject Request) result touchManagedPtr _obj touchManagedPtr uri return result' ) (do return () ) -- method Session::requeue_message -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_session_requeue_message" soup_session_requeue_message :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr Message -> -- msg : TInterface "Soup" "Message" IO () sessionRequeueMessage :: (MonadIO m, SessionK a, MessageK b) => a -> -- _obj b -> -- msg m () sessionRequeueMessage _obj msg = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg soup_session_requeue_message _obj' msg' touchManagedPtr _obj touchManagedPtr msg return () -- method Session::send -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Gio" "InputStream" -- throws : True -- Skip return : False foreign import ccall "soup_session_send" soup_session_send :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr Message -> -- msg : TInterface "Soup" "Message" Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" Ptr (Ptr GError) -> -- error IO (Ptr Gio.InputStream) sessionSend :: (MonadIO m, SessionK a, MessageK b, Gio.CancellableK c) => a -> -- _obj b -> -- msg Maybe (c) -> -- cancellable m Gio.InputStream sessionSend _obj msg cancellable = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' onException (do result <- propagateGError $ soup_session_send _obj' msg' maybeCancellable checkUnexpectedReturnNULL "soup_session_send" result result' <- (wrapObject Gio.InputStream) result touchManagedPtr _obj touchManagedPtr msg whenJust cancellable touchManagedPtr return result' ) (do return () ) -- method Session::send_async -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 4, 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" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 4, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_session_send_async" soup_session_send_async :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr Message -> -- msg : TInterface "Soup" "Message" Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" FunPtr Gio.AsyncReadyCallbackC -> -- callback : TInterface "Gio" "AsyncReadyCallback" Ptr () -> -- user_data : TBasicType TVoid IO () sessionSendAsync :: (MonadIO m, SessionK a, MessageK b, Gio.CancellableK c) => a -> -- _obj b -> -- msg Maybe (c) -> -- cancellable Maybe (Gio.AsyncReadyCallback) -> -- callback m () sessionSendAsync _obj msg cancellable callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' ptrcallback <- callocMem :: IO (Ptr (FunPtr Gio.AsyncReadyCallbackC)) maybeCallback <- case callback of Nothing -> return (castPtrToFunPtr nullPtr) Just jCallback -> do jCallback' <- Gio.mkAsyncReadyCallback (Gio.asyncReadyCallbackWrapper (Just ptrcallback) jCallback) poke ptrcallback jCallback' return jCallback' let user_data = nullPtr soup_session_send_async _obj' msg' maybeCancellable maybeCallback user_data touchManagedPtr _obj touchManagedPtr msg whenJust cancellable touchManagedPtr return () -- method Session::send_finish -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Gio" "InputStream" -- throws : True -- Skip return : False foreign import ccall "soup_session_send_finish" soup_session_send_finish :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr Gio.AsyncResult -> -- result : TInterface "Gio" "AsyncResult" Ptr (Ptr GError) -> -- error IO (Ptr Gio.InputStream) sessionSendFinish :: (MonadIO m, SessionK a, Gio.AsyncResultK b) => a -> -- _obj b -> -- result m Gio.InputStream sessionSendFinish _obj result_ = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let result_' = unsafeManagedPtrCastPtr result_ onException (do result <- propagateGError $ soup_session_send_finish _obj' result_' checkUnexpectedReturnNULL "soup_session_send_finish" result result' <- (wrapObject Gio.InputStream) result touchManagedPtr _obj touchManagedPtr result_ return result' ) (do return () ) -- method Session::send_message -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_session_send_message" soup_session_send_message :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr Message -> -- msg : TInterface "Soup" "Message" IO Word32 sessionSendMessage :: (MonadIO m, SessionK a, MessageK b) => a -> -- _obj b -> -- msg m Word32 sessionSendMessage _obj msg = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg result <- soup_session_send_message _obj' msg' touchManagedPtr _obj touchManagedPtr msg return result -- method Session::steal_connection -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Gio" "IOStream" -- throws : False -- Skip return : False foreign import ccall "soup_session_steal_connection" soup_session_steal_connection :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr Message -> -- msg : TInterface "Soup" "Message" IO (Ptr Gio.IOStream) sessionStealConnection :: (MonadIO m, SessionK a, MessageK b) => a -> -- _obj b -> -- msg m Gio.IOStream sessionStealConnection _obj msg = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg result <- soup_session_steal_connection _obj' msg' checkUnexpectedReturnNULL "soup_session_steal_connection" result result' <- (wrapObject Gio.IOStream) result touchManagedPtr _obj touchManagedPtr msg return result' -- method Session::unpause_message -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_session_unpause_message" soup_session_unpause_message :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr Message -> -- msg : TInterface "Soup" "Message" IO () sessionUnpauseMessage :: (MonadIO m, SessionK a, MessageK b) => a -> -- _obj b -> -- msg m () sessionUnpauseMessage _obj msg = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg soup_session_unpause_message _obj' msg' touchManagedPtr _obj touchManagedPtr msg return () -- method Session::websocket_connect_async -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "origin", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "protocols", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 6, 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" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "origin", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "protocols", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gio" "AsyncReadyCallback", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 6, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_session_websocket_connect_async" soup_session_websocket_connect_async :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr Message -> -- msg : TInterface "Soup" "Message" CString -> -- origin : TBasicType TUTF8 Ptr CString -> -- protocols : TCArray True (-1) (-1) (TBasicType TUTF8) Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" FunPtr Gio.AsyncReadyCallbackC -> -- callback : TInterface "Gio" "AsyncReadyCallback" Ptr () -> -- user_data : TBasicType TVoid IO () sessionWebsocketConnectAsync :: (MonadIO m, SessionK a, MessageK b, Gio.CancellableK c) => a -> -- _obj b -> -- msg Maybe (T.Text) -> -- origin Maybe ([T.Text]) -> -- protocols Maybe (c) -> -- cancellable Maybe (Gio.AsyncReadyCallback) -> -- callback m () sessionWebsocketConnectAsync _obj msg origin protocols cancellable callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg maybeOrigin <- case origin of Nothing -> return nullPtr Just jOrigin -> do jOrigin' <- textToCString jOrigin return jOrigin' maybeProtocols <- case protocols of Nothing -> return nullPtr Just jProtocols -> do jProtocols' <- packZeroTerminatedUTF8CArray jProtocols return jProtocols' maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' ptrcallback <- callocMem :: IO (Ptr (FunPtr Gio.AsyncReadyCallbackC)) maybeCallback <- case callback of Nothing -> return (castPtrToFunPtr nullPtr) Just jCallback -> do jCallback' <- Gio.mkAsyncReadyCallback (Gio.asyncReadyCallbackWrapper (Just ptrcallback) jCallback) poke ptrcallback jCallback' return jCallback' let user_data = nullPtr soup_session_websocket_connect_async _obj' msg' maybeOrigin maybeProtocols maybeCancellable maybeCallback user_data touchManagedPtr _obj touchManagedPtr msg whenJust cancellable touchManagedPtr freeMem maybeOrigin mapZeroTerminatedCArray freeMem maybeProtocols freeMem maybeProtocols return () -- method Session::websocket_connect_finish -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TInterface "Gio" "AsyncResult", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "WebsocketConnection" -- throws : True -- Skip return : False foreign import ccall "soup_session_websocket_connect_finish" soup_session_websocket_connect_finish :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr Gio.AsyncResult -> -- result : TInterface "Gio" "AsyncResult" Ptr (Ptr GError) -> -- error IO (Ptr WebsocketConnection) sessionWebsocketConnectFinish :: (MonadIO m, SessionK a, Gio.AsyncResultK b) => a -> -- _obj b -> -- result m WebsocketConnection sessionWebsocketConnectFinish _obj result_ = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let result_' = unsafeManagedPtrCastPtr result_ onException (do result <- propagateGError $ soup_session_websocket_connect_finish _obj' result_' checkUnexpectedReturnNULL "soup_session_websocket_connect_finish" result result' <- (wrapObject WebsocketConnection) result touchManagedPtr _obj touchManagedPtr result_ return result' ) (do return () ) -- method Session::would_redirect -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_session_would_redirect" soup_session_would_redirect :: Ptr Session -> -- _obj : TInterface "Soup" "Session" Ptr Message -> -- msg : TInterface "Soup" "Message" IO CInt sessionWouldRedirect :: (MonadIO m, SessionK a, MessageK b) => a -> -- _obj b -> -- msg m Bool sessionWouldRedirect _obj msg = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let msg' = unsafeManagedPtrCastPtr msg result <- soup_session_would_redirect _obj' msg' let result' = (/= 0) result touchManagedPtr _obj touchManagedPtr msg return result' -- signal Session::authenticate type SessionAuthenticateCallback = Message -> Auth -> Bool -> IO () noSessionAuthenticateCallback :: Maybe SessionAuthenticateCallback noSessionAuthenticateCallback = Nothing type SessionAuthenticateCallbackC = Ptr () -> -- object Ptr Message -> Ptr Auth -> CInt -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkSessionAuthenticateCallback :: SessionAuthenticateCallbackC -> IO (FunPtr SessionAuthenticateCallbackC) sessionAuthenticateClosure :: SessionAuthenticateCallback -> IO Closure sessionAuthenticateClosure cb = newCClosure =<< mkSessionAuthenticateCallback wrapped where wrapped = sessionAuthenticateCallbackWrapper cb sessionAuthenticateCallbackWrapper :: SessionAuthenticateCallback -> Ptr () -> Ptr Message -> Ptr Auth -> CInt -> Ptr () -> IO () sessionAuthenticateCallbackWrapper _cb _ msg auth retrying _ = do msg' <- (newObject Message) msg auth' <- (newObject Auth) auth let retrying' = (/= 0) retrying _cb msg' auth' retrying' onSessionAuthenticate :: (GObject a, MonadIO m) => a -> SessionAuthenticateCallback -> m SignalHandlerId onSessionAuthenticate obj cb = liftIO $ connectSessionAuthenticate obj cb SignalConnectBefore afterSessionAuthenticate :: (GObject a, MonadIO m) => a -> SessionAuthenticateCallback -> m SignalHandlerId afterSessionAuthenticate obj cb = connectSessionAuthenticate obj cb SignalConnectAfter connectSessionAuthenticate :: (GObject a, MonadIO m) => a -> SessionAuthenticateCallback -> SignalConnectMode -> m SignalHandlerId connectSessionAuthenticate obj cb after = liftIO $ do cb' <- mkSessionAuthenticateCallback (sessionAuthenticateCallbackWrapper cb) connectSignalFunPtr obj "authenticate" cb' after -- signal Session::connection-created type SessionConnectionCreatedCallback = GObject.Object -> IO () noSessionConnectionCreatedCallback :: Maybe SessionConnectionCreatedCallback noSessionConnectionCreatedCallback = Nothing type SessionConnectionCreatedCallbackC = Ptr () -> -- object Ptr GObject.Object -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkSessionConnectionCreatedCallback :: SessionConnectionCreatedCallbackC -> IO (FunPtr SessionConnectionCreatedCallbackC) sessionConnectionCreatedClosure :: SessionConnectionCreatedCallback -> IO Closure sessionConnectionCreatedClosure cb = newCClosure =<< mkSessionConnectionCreatedCallback wrapped where wrapped = sessionConnectionCreatedCallbackWrapper cb sessionConnectionCreatedCallbackWrapper :: SessionConnectionCreatedCallback -> Ptr () -> Ptr GObject.Object -> Ptr () -> IO () sessionConnectionCreatedCallbackWrapper _cb _ connection _ = do connection' <- (newObject GObject.Object) connection _cb connection' onSessionConnectionCreated :: (GObject a, MonadIO m) => a -> SessionConnectionCreatedCallback -> m SignalHandlerId onSessionConnectionCreated obj cb = liftIO $ connectSessionConnectionCreated obj cb SignalConnectBefore afterSessionConnectionCreated :: (GObject a, MonadIO m) => a -> SessionConnectionCreatedCallback -> m SignalHandlerId afterSessionConnectionCreated obj cb = connectSessionConnectionCreated obj cb SignalConnectAfter connectSessionConnectionCreated :: (GObject a, MonadIO m) => a -> SessionConnectionCreatedCallback -> SignalConnectMode -> m SignalHandlerId connectSessionConnectionCreated obj cb after = liftIO $ do cb' <- mkSessionConnectionCreatedCallback (sessionConnectionCreatedCallbackWrapper cb) connectSignalFunPtr obj "connection-created" cb' after -- signal Session::request-queued type SessionRequestQueuedCallback = Message -> IO () noSessionRequestQueuedCallback :: Maybe SessionRequestQueuedCallback noSessionRequestQueuedCallback = Nothing type SessionRequestQueuedCallbackC = Ptr () -> -- object Ptr Message -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkSessionRequestQueuedCallback :: SessionRequestQueuedCallbackC -> IO (FunPtr SessionRequestQueuedCallbackC) sessionRequestQueuedClosure :: SessionRequestQueuedCallback -> IO Closure sessionRequestQueuedClosure cb = newCClosure =<< mkSessionRequestQueuedCallback wrapped where wrapped = sessionRequestQueuedCallbackWrapper cb sessionRequestQueuedCallbackWrapper :: SessionRequestQueuedCallback -> Ptr () -> Ptr Message -> Ptr () -> IO () sessionRequestQueuedCallbackWrapper _cb _ msg _ = do msg' <- (newObject Message) msg _cb msg' onSessionRequestQueued :: (GObject a, MonadIO m) => a -> SessionRequestQueuedCallback -> m SignalHandlerId onSessionRequestQueued obj cb = liftIO $ connectSessionRequestQueued obj cb SignalConnectBefore afterSessionRequestQueued :: (GObject a, MonadIO m) => a -> SessionRequestQueuedCallback -> m SignalHandlerId afterSessionRequestQueued obj cb = connectSessionRequestQueued obj cb SignalConnectAfter connectSessionRequestQueued :: (GObject a, MonadIO m) => a -> SessionRequestQueuedCallback -> SignalConnectMode -> m SignalHandlerId connectSessionRequestQueued obj cb after = liftIO $ do cb' <- mkSessionRequestQueuedCallback (sessionRequestQueuedCallbackWrapper cb) connectSignalFunPtr obj "request-queued" cb' after -- signal Session::request-started type SessionRequestStartedCallback = Message -> Socket -> IO () noSessionRequestStartedCallback :: Maybe SessionRequestStartedCallback noSessionRequestStartedCallback = Nothing type SessionRequestStartedCallbackC = Ptr () -> -- object Ptr Message -> Ptr Socket -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkSessionRequestStartedCallback :: SessionRequestStartedCallbackC -> IO (FunPtr SessionRequestStartedCallbackC) sessionRequestStartedClosure :: SessionRequestStartedCallback -> IO Closure sessionRequestStartedClosure cb = newCClosure =<< mkSessionRequestStartedCallback wrapped where wrapped = sessionRequestStartedCallbackWrapper cb sessionRequestStartedCallbackWrapper :: SessionRequestStartedCallback -> Ptr () -> Ptr Message -> Ptr Socket -> Ptr () -> IO () sessionRequestStartedCallbackWrapper _cb _ msg socket _ = do msg' <- (newObject Message) msg socket' <- (newObject Socket) socket _cb msg' socket' onSessionRequestStarted :: (GObject a, MonadIO m) => a -> SessionRequestStartedCallback -> m SignalHandlerId onSessionRequestStarted obj cb = liftIO $ connectSessionRequestStarted obj cb SignalConnectBefore afterSessionRequestStarted :: (GObject a, MonadIO m) => a -> SessionRequestStartedCallback -> m SignalHandlerId afterSessionRequestStarted obj cb = connectSessionRequestStarted obj cb SignalConnectAfter connectSessionRequestStarted :: (GObject a, MonadIO m) => a -> SessionRequestStartedCallback -> SignalConnectMode -> m SignalHandlerId connectSessionRequestStarted obj cb after = liftIO $ do cb' <- mkSessionRequestStartedCallback (sessionRequestStartedCallbackWrapper cb) connectSignalFunPtr obj "request-started" cb' after -- signal Session::request-unqueued type SessionRequestUnqueuedCallback = Message -> IO () noSessionRequestUnqueuedCallback :: Maybe SessionRequestUnqueuedCallback noSessionRequestUnqueuedCallback = Nothing type SessionRequestUnqueuedCallbackC = Ptr () -> -- object Ptr Message -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkSessionRequestUnqueuedCallback :: SessionRequestUnqueuedCallbackC -> IO (FunPtr SessionRequestUnqueuedCallbackC) sessionRequestUnqueuedClosure :: SessionRequestUnqueuedCallback -> IO Closure sessionRequestUnqueuedClosure cb = newCClosure =<< mkSessionRequestUnqueuedCallback wrapped where wrapped = sessionRequestUnqueuedCallbackWrapper cb sessionRequestUnqueuedCallbackWrapper :: SessionRequestUnqueuedCallback -> Ptr () -> Ptr Message -> Ptr () -> IO () sessionRequestUnqueuedCallbackWrapper _cb _ msg _ = do msg' <- (newObject Message) msg _cb msg' onSessionRequestUnqueued :: (GObject a, MonadIO m) => a -> SessionRequestUnqueuedCallback -> m SignalHandlerId onSessionRequestUnqueued obj cb = liftIO $ connectSessionRequestUnqueued obj cb SignalConnectBefore afterSessionRequestUnqueued :: (GObject a, MonadIO m) => a -> SessionRequestUnqueuedCallback -> m SignalHandlerId afterSessionRequestUnqueued obj cb = connectSessionRequestUnqueued obj cb SignalConnectAfter connectSessionRequestUnqueued :: (GObject a, MonadIO m) => a -> SessionRequestUnqueuedCallback -> SignalConnectMode -> m SignalHandlerId connectSessionRequestUnqueued obj cb after = liftIO $ do cb' <- mkSessionRequestUnqueuedCallback (sessionRequestUnqueuedCallbackWrapper cb) connectSignalFunPtr obj "request-unqueued" cb' after -- signal Session::tunneling type SessionTunnelingCallback = GObject.Object -> IO () noSessionTunnelingCallback :: Maybe SessionTunnelingCallback noSessionTunnelingCallback = Nothing type SessionTunnelingCallbackC = Ptr () -> -- object Ptr GObject.Object -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkSessionTunnelingCallback :: SessionTunnelingCallbackC -> IO (FunPtr SessionTunnelingCallbackC) sessionTunnelingClosure :: SessionTunnelingCallback -> IO Closure sessionTunnelingClosure cb = newCClosure =<< mkSessionTunnelingCallback wrapped where wrapped = sessionTunnelingCallbackWrapper cb sessionTunnelingCallbackWrapper :: SessionTunnelingCallback -> Ptr () -> Ptr GObject.Object -> Ptr () -> IO () sessionTunnelingCallbackWrapper _cb _ connection _ = do connection' <- (newObject GObject.Object) connection _cb connection' onSessionTunneling :: (GObject a, MonadIO m) => a -> SessionTunnelingCallback -> m SignalHandlerId onSessionTunneling obj cb = liftIO $ connectSessionTunneling obj cb SignalConnectBefore afterSessionTunneling :: (GObject a, MonadIO m) => a -> SessionTunnelingCallback -> m SignalHandlerId afterSessionTunneling obj cb = connectSessionTunneling obj cb SignalConnectAfter connectSessionTunneling :: (GObject a, MonadIO m) => a -> SessionTunnelingCallback -> SignalConnectMode -> m SignalHandlerId connectSessionTunneling obj cb after = liftIO $ do cb' <- mkSessionTunnelingCallback (sessionTunnelingCallbackWrapper cb) connectSignalFunPtr obj "tunneling" cb' after -- object SessionAsync newtype SessionAsync = SessionAsync (ForeignPtr SessionAsync) noSessionAsync :: Maybe SessionAsync noSessionAsync = Nothing foreign import ccall "soup_session_async_get_type" c_soup_session_async_get_type :: IO GType type instance ParentTypes SessionAsync = '[Session, GObject.Object] instance GObject SessionAsync where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_session_async_get_type class GObject o => SessionAsyncK o instance (GObject o, IsDescendantOf SessionAsync o) => SessionAsyncK o toSessionAsync :: SessionAsyncK o => o -> IO SessionAsync toSessionAsync = unsafeCastTo SessionAsync -- method SessionAsync::new -- method type : Constructor -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TInterface "Soup" "SessionAsync" -- throws : False -- Skip return : False foreign import ccall "soup_session_async_new" soup_session_async_new :: IO (Ptr SessionAsync) {-# DEPRECATED sessionAsyncNew ["#SoupSessionAsync is deprecated; use a plain","#SoupSession, created with soup_session_new(). See the porting guide."]#-} sessionAsyncNew :: (MonadIO m) => m SessionAsync sessionAsyncNew = liftIO $ do result <- soup_session_async_new checkUnexpectedReturnNULL "soup_session_async_new" result result' <- (wrapObject SessionAsync) result return result' -- callback SessionCallback sessionCallbackClosure :: SessionCallback -> IO Closure sessionCallbackClosure cb = newCClosure =<< mkSessionCallback wrapped where wrapped = sessionCallbackWrapper Nothing cb type SessionCallbackC = Ptr Session -> Ptr Message -> Ptr () -> IO () foreign import ccall "wrapper" mkSessionCallback :: SessionCallbackC -> IO (FunPtr SessionCallbackC) type SessionCallback = Session -> Message -> IO () noSessionCallback :: Maybe SessionCallback noSessionCallback = Nothing sessionCallbackWrapper :: Maybe (Ptr (FunPtr (SessionCallbackC))) -> SessionCallback -> Ptr Session -> Ptr Message -> Ptr () -> IO () sessionCallbackWrapper funptrptr _cb session msg _ = do session' <- (newObject Session) session msg' <- (newObject Message) msg _cb session' msg' maybeReleaseFunPtr funptrptr -- interface SessionFeature newtype SessionFeature = SessionFeature (ForeignPtr SessionFeature) noSessionFeature :: Maybe SessionFeature noSessionFeature = Nothing foreign import ccall "soup_session_feature_get_type" c_soup_session_feature_get_type :: IO GType type instance ParentTypes SessionFeature = '[GObject.Object] instance GObject SessionFeature where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_session_feature_get_type class GObject o => SessionFeatureK o instance (GObject o, IsDescendantOf SessionFeature o) => SessionFeatureK o toSessionFeature :: SessionFeatureK o => o -> IO SessionFeature toSessionFeature = unsafeCastTo SessionFeature -- method SessionFeature::add_feature -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "SessionFeature", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "SessionFeature", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_session_feature_add_feature" soup_session_feature_add_feature :: Ptr SessionFeature -> -- _obj : TInterface "Soup" "SessionFeature" CGType -> -- type : TBasicType TGType IO CInt sessionFeatureAddFeature :: (MonadIO m, SessionFeatureK a) => a -> -- _obj GType -> -- type m Bool sessionFeatureAddFeature _obj type_ = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let type_' = gtypeToCGType type_ result <- soup_session_feature_add_feature _obj' type_' let result' = (/= 0) result touchManagedPtr _obj return result' -- method SessionFeature::attach -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "SessionFeature", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "session", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "SessionFeature", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "session", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_session_feature_attach" soup_session_feature_attach :: Ptr SessionFeature -> -- _obj : TInterface "Soup" "SessionFeature" Ptr Session -> -- session : TInterface "Soup" "Session" IO () sessionFeatureAttach :: (MonadIO m, SessionFeatureK a, SessionK b) => a -> -- _obj b -> -- session m () sessionFeatureAttach _obj session = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let session' = unsafeManagedPtrCastPtr session soup_session_feature_attach _obj' session' touchManagedPtr _obj touchManagedPtr session return () -- method SessionFeature::detach -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "SessionFeature", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "session", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "SessionFeature", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "session", argType = TInterface "Soup" "Session", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_session_feature_detach" soup_session_feature_detach :: Ptr SessionFeature -> -- _obj : TInterface "Soup" "SessionFeature" Ptr Session -> -- session : TInterface "Soup" "Session" IO () sessionFeatureDetach :: (MonadIO m, SessionFeatureK a, SessionK b) => a -> -- _obj b -> -- session m () sessionFeatureDetach _obj session = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let session' = unsafeManagedPtrCastPtr session soup_session_feature_detach _obj' session' touchManagedPtr _obj touchManagedPtr session return () -- method SessionFeature::has_feature -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "SessionFeature", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "SessionFeature", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_session_feature_has_feature" soup_session_feature_has_feature :: Ptr SessionFeature -> -- _obj : TInterface "Soup" "SessionFeature" CGType -> -- type : TBasicType TGType IO CInt sessionFeatureHasFeature :: (MonadIO m, SessionFeatureK a) => a -> -- _obj GType -> -- type m Bool sessionFeatureHasFeature _obj type_ = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let type_' = gtypeToCGType type_ result <- soup_session_feature_has_feature _obj' type_' let result' = (/= 0) result touchManagedPtr _obj return result' -- method SessionFeature::remove_feature -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "SessionFeature", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "SessionFeature", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_session_feature_remove_feature" soup_session_feature_remove_feature :: Ptr SessionFeature -> -- _obj : TInterface "Soup" "SessionFeature" CGType -> -- type : TBasicType TGType IO CInt sessionFeatureRemoveFeature :: (MonadIO m, SessionFeatureK a) => a -> -- _obj GType -> -- type m Bool sessionFeatureRemoveFeature _obj type_ = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj let type_' = gtypeToCGType type_ result <- soup_session_feature_remove_feature _obj' type_' let result' = (/= 0) result touchManagedPtr _obj return result' -- object SessionSync newtype SessionSync = SessionSync (ForeignPtr SessionSync) noSessionSync :: Maybe SessionSync noSessionSync = Nothing foreign import ccall "soup_session_sync_get_type" c_soup_session_sync_get_type :: IO GType type instance ParentTypes SessionSync = '[Session, GObject.Object] instance GObject SessionSync where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_session_sync_get_type class GObject o => SessionSyncK o instance (GObject o, IsDescendantOf SessionSync o) => SessionSyncK o toSessionSync :: SessionSyncK o => o -> IO SessionSync toSessionSync = unsafeCastTo SessionSync -- method SessionSync::new -- method type : Constructor -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TInterface "Soup" "SessionSync" -- throws : False -- Skip return : False foreign import ccall "soup_session_sync_new" soup_session_sync_new :: IO (Ptr SessionSync) {-# DEPRECATED sessionSyncNew ["#SoupSessionSync is deprecated; use a plain","#SoupSession, created with soup_session_new(). See the porting guide."]#-} sessionSyncNew :: (MonadIO m) => m SessionSync sessionSyncNew = liftIO $ do result <- soup_session_sync_new checkUnexpectedReturnNULL "soup_session_sync_new" result result' <- (wrapObject SessionSync) result return result' -- object Socket newtype Socket = Socket (ForeignPtr Socket) noSocket :: Maybe Socket noSocket = Nothing foreign import ccall "soup_socket_get_type" c_soup_socket_get_type :: IO GType type instance ParentTypes Socket = '[GObject.Object, Gio.Initable] instance GObject Socket where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_socket_get_type class GObject o => SocketK o instance (GObject o, IsDescendantOf Socket o) => SocketK o toSocket :: SocketK o => o -> IO Socket toSocket = unsafeCastTo Socket -- method Socket::connect_async -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "SocketCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = 3, 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" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Soup" "SocketCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = 3, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_socket_connect_async" soup_socket_connect_async :: Ptr Socket -> -- _obj : TInterface "Soup" "Socket" Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" FunPtr SocketCallbackC -> -- callback : TInterface "Soup" "SocketCallback" Ptr () -> -- user_data : TBasicType TVoid IO () socketConnectAsync :: (MonadIO m, SocketK a, Gio.CancellableK b) => a -> -- _obj Maybe (b) -> -- cancellable SocketCallback -> -- callback m () socketConnectAsync _obj cancellable callback = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' ptrcallback <- callocMem :: IO (Ptr (FunPtr SocketCallbackC)) callback' <- mkSocketCallback (socketCallbackWrapper (Just ptrcallback) callback) poke ptrcallback callback' let user_data = nullPtr soup_socket_connect_async _obj' maybeCancellable callback' user_data touchManagedPtr _obj whenJust cancellable touchManagedPtr return () -- method Socket::connect_sync -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_socket_connect_sync" soup_socket_connect_sync :: Ptr Socket -> -- _obj : TInterface "Soup" "Socket" Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" IO Word32 socketConnectSync :: (MonadIO m, SocketK a, Gio.CancellableK b) => a -> -- _obj Maybe (b) -> -- cancellable m Word32 socketConnectSync _obj cancellable = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' result <- soup_socket_connect_sync _obj' maybeCancellable touchManagedPtr _obj whenJust cancellable touchManagedPtr return result -- method Socket::disconnect -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_socket_disconnect" soup_socket_disconnect :: Ptr Socket -> -- _obj : TInterface "Soup" "Socket" IO () socketDisconnect :: (MonadIO m, SocketK a) => a -> -- _obj m () socketDisconnect _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj soup_socket_disconnect _obj' touchManagedPtr _obj return () -- method Socket::get_fd -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TInt32 -- throws : False -- Skip return : False foreign import ccall "soup_socket_get_fd" soup_socket_get_fd :: Ptr Socket -> -- _obj : TInterface "Soup" "Socket" IO Int32 socketGetFd :: (MonadIO m, SocketK a) => a -> -- _obj m Int32 socketGetFd _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_socket_get_fd _obj' touchManagedPtr _obj return result -- method Socket::get_local_address -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Address" -- throws : False -- Skip return : False foreign import ccall "soup_socket_get_local_address" soup_socket_get_local_address :: Ptr Socket -> -- _obj : TInterface "Soup" "Socket" IO (Ptr Address) socketGetLocalAddress :: (MonadIO m, SocketK a) => a -> -- _obj m Address socketGetLocalAddress _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_socket_get_local_address _obj' checkUnexpectedReturnNULL "soup_socket_get_local_address" result result' <- (newObject Address) result touchManagedPtr _obj return result' -- method Socket::get_remote_address -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Address" -- throws : False -- Skip return : False foreign import ccall "soup_socket_get_remote_address" soup_socket_get_remote_address :: Ptr Socket -> -- _obj : TInterface "Soup" "Socket" IO (Ptr Address) socketGetRemoteAddress :: (MonadIO m, SocketK a) => a -> -- _obj m Address socketGetRemoteAddress _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_socket_get_remote_address _obj' checkUnexpectedReturnNULL "soup_socket_get_remote_address" result result' <- (newObject Address) result touchManagedPtr _obj return result' -- method Socket::is_connected -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_socket_is_connected" soup_socket_is_connected :: Ptr Socket -> -- _obj : TInterface "Soup" "Socket" IO CInt socketIsConnected :: (MonadIO m, SocketK a) => a -> -- _obj m Bool socketIsConnected _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_socket_is_connected _obj' let result' = (/= 0) result touchManagedPtr _obj return result' -- method Socket::is_ssl -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_socket_is_ssl" soup_socket_is_ssl :: Ptr Socket -> -- _obj : TInterface "Soup" "Socket" IO CInt socketIsSsl :: (MonadIO m, SocketK a) => a -> -- _obj m Bool socketIsSsl _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_socket_is_ssl _obj' let result' = (/= 0) result touchManagedPtr _obj return result' -- method Socket::listen -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_socket_listen" soup_socket_listen :: Ptr Socket -> -- _obj : TInterface "Soup" "Socket" IO CInt socketListen :: (MonadIO m, SocketK a) => a -> -- _obj m Bool socketListen _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_socket_listen _obj' let result' = (/= 0) result touchManagedPtr _obj return result' -- method Socket::read -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "nread", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [Arg {argName = "len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "SocketIOStatus" -- throws : True -- Skip return : False foreign import ccall "soup_socket_read" soup_socket_read :: Ptr Socket -> -- _obj : TInterface "Soup" "Socket" Ptr Word8 -> -- buffer : TCArray False (-1) 2 (TBasicType TUInt8) Word64 -> -- len : TBasicType TUInt64 Ptr Word64 -> -- nread : TBasicType TUInt64 Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" Ptr (Ptr GError) -> -- error IO CUInt socketRead :: (MonadIO m, SocketK a, Gio.CancellableK b) => a -> -- _obj ByteString -> -- buffer Maybe (b) -> -- cancellable m (SocketIOStatus,Word64) socketRead _obj buffer cancellable = liftIO $ do let len = fromIntegral $ B.length buffer let _obj' = unsafeManagedPtrCastPtr _obj buffer' <- packByteString buffer nread <- allocMem :: IO (Ptr Word64) maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' onException (do result <- propagateGError $ soup_socket_read _obj' buffer' len nread maybeCancellable let result' = (toEnum . fromIntegral) result nread' <- peek nread touchManagedPtr _obj whenJust cancellable touchManagedPtr freeMem buffer' freeMem nread return (result', nread') ) (do freeMem buffer' freeMem nread ) -- method Socket::read_until -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "boundary", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "boundary_len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "nread", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "got_boundary", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [Arg {argName = "len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "boundary", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "boundary_len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "got_boundary", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "SocketIOStatus" -- throws : True -- Skip return : False foreign import ccall "soup_socket_read_until" soup_socket_read_until :: Ptr Socket -> -- _obj : TInterface "Soup" "Socket" Ptr Word8 -> -- buffer : TCArray False (-1) 2 (TBasicType TUInt8) Word64 -> -- len : TBasicType TUInt64 Ptr () -> -- boundary : TBasicType TVoid Word64 -> -- boundary_len : TBasicType TUInt64 Ptr Word64 -> -- nread : TBasicType TUInt64 CInt -> -- got_boundary : TBasicType TBoolean Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" Ptr (Ptr GError) -> -- error IO CUInt socketReadUntil :: (MonadIO m, SocketK a, Gio.CancellableK b) => a -> -- _obj ByteString -> -- buffer Ptr () -> -- boundary Word64 -> -- boundary_len Bool -> -- got_boundary Maybe (b) -> -- cancellable m (SocketIOStatus,Word64) socketReadUntil _obj buffer boundary boundary_len got_boundary cancellable = liftIO $ do let len = fromIntegral $ B.length buffer let _obj' = unsafeManagedPtrCastPtr _obj buffer' <- packByteString buffer nread <- allocMem :: IO (Ptr Word64) let got_boundary' = (fromIntegral . fromEnum) got_boundary maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' onException (do result <- propagateGError $ soup_socket_read_until _obj' buffer' len boundary boundary_len nread got_boundary' maybeCancellable let result' = (toEnum . fromIntegral) result nread' <- peek nread touchManagedPtr _obj whenJust cancellable touchManagedPtr freeMem buffer' freeMem nread return (result', nread') ) (do freeMem buffer' freeMem nread ) -- method Socket::start_proxy_ssl -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ssl_host", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ssl_host", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_socket_start_proxy_ssl" soup_socket_start_proxy_ssl :: Ptr Socket -> -- _obj : TInterface "Soup" "Socket" CString -> -- ssl_host : TBasicType TUTF8 Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" IO CInt socketStartProxySsl :: (MonadIO m, SocketK a, Gio.CancellableK b) => a -> -- _obj T.Text -> -- ssl_host Maybe (b) -> -- cancellable m Bool socketStartProxySsl _obj ssl_host cancellable = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj ssl_host' <- textToCString ssl_host maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' result <- soup_socket_start_proxy_ssl _obj' ssl_host' maybeCancellable let result' = (/= 0) result touchManagedPtr _obj whenJust cancellable touchManagedPtr freeMem ssl_host' return result' -- method Socket::start_ssl -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_socket_start_ssl" soup_socket_start_ssl :: Ptr Socket -> -- _obj : TInterface "Soup" "Socket" Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" IO CInt socketStartSsl :: (MonadIO m, SocketK a, Gio.CancellableK b) => a -> -- _obj Maybe (b) -> -- cancellable m Bool socketStartSsl _obj cancellable = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' result <- soup_socket_start_ssl _obj' maybeCancellable let result' = (/= 0) result touchManagedPtr _obj whenJust cancellable touchManagedPtr return result' -- method Socket::write -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "nwrote", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [Arg {argName = "len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "Socket", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buffer", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cancellable", argType = TInterface "Gio" "Cancellable", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "SocketIOStatus" -- throws : True -- Skip return : False foreign import ccall "soup_socket_write" soup_socket_write :: Ptr Socket -> -- _obj : TInterface "Soup" "Socket" Ptr Word8 -> -- buffer : TCArray False (-1) 2 (TBasicType TUInt8) Word64 -> -- len : TBasicType TUInt64 Ptr Word64 -> -- nwrote : TBasicType TUInt64 Ptr Gio.Cancellable -> -- cancellable : TInterface "Gio" "Cancellable" Ptr (Ptr GError) -> -- error IO CUInt socketWrite :: (MonadIO m, SocketK a, Gio.CancellableK b) => a -> -- _obj ByteString -> -- buffer Maybe (b) -> -- cancellable m (SocketIOStatus,Word64) socketWrite _obj buffer cancellable = liftIO $ do let len = fromIntegral $ B.length buffer let _obj' = unsafeManagedPtrCastPtr _obj buffer' <- packByteString buffer nwrote <- allocMem :: IO (Ptr Word64) maybeCancellable <- case cancellable of Nothing -> return nullPtr Just jCancellable -> do let jCancellable' = unsafeManagedPtrCastPtr jCancellable return jCancellable' onException (do result <- propagateGError $ soup_socket_write _obj' buffer' len nwrote maybeCancellable let result' = (toEnum . fromIntegral) result nwrote' <- peek nwrote touchManagedPtr _obj whenJust cancellable touchManagedPtr freeMem buffer' freeMem nwrote return (result', nwrote') ) (do freeMem buffer' freeMem nwrote ) -- signal Socket::disconnected type SocketDisconnectedCallback = IO () noSocketDisconnectedCallback :: Maybe SocketDisconnectedCallback noSocketDisconnectedCallback = Nothing type SocketDisconnectedCallbackC = Ptr () -> -- object Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkSocketDisconnectedCallback :: SocketDisconnectedCallbackC -> IO (FunPtr SocketDisconnectedCallbackC) socketDisconnectedClosure :: SocketDisconnectedCallback -> IO Closure socketDisconnectedClosure cb = newCClosure =<< mkSocketDisconnectedCallback wrapped where wrapped = socketDisconnectedCallbackWrapper cb socketDisconnectedCallbackWrapper :: SocketDisconnectedCallback -> Ptr () -> Ptr () -> IO () socketDisconnectedCallbackWrapper _cb _ _ = do _cb onSocketDisconnected :: (GObject a, MonadIO m) => a -> SocketDisconnectedCallback -> m SignalHandlerId onSocketDisconnected obj cb = liftIO $ connectSocketDisconnected obj cb SignalConnectBefore afterSocketDisconnected :: (GObject a, MonadIO m) => a -> SocketDisconnectedCallback -> m SignalHandlerId afterSocketDisconnected obj cb = connectSocketDisconnected obj cb SignalConnectAfter connectSocketDisconnected :: (GObject a, MonadIO m) => a -> SocketDisconnectedCallback -> SignalConnectMode -> m SignalHandlerId connectSocketDisconnected obj cb after = liftIO $ do cb' <- mkSocketDisconnectedCallback (socketDisconnectedCallbackWrapper cb) connectSignalFunPtr obj "disconnected" cb' after -- signal Socket::event type SocketEventCallback = Gio.SocketClientEvent -> Gio.IOStream -> IO () noSocketEventCallback :: Maybe SocketEventCallback noSocketEventCallback = Nothing type SocketEventCallbackC = Ptr () -> -- object CUInt -> Ptr Gio.IOStream -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkSocketEventCallback :: SocketEventCallbackC -> IO (FunPtr SocketEventCallbackC) socketEventClosure :: SocketEventCallback -> IO Closure socketEventClosure cb = newCClosure =<< mkSocketEventCallback wrapped where wrapped = socketEventCallbackWrapper cb socketEventCallbackWrapper :: SocketEventCallback -> Ptr () -> CUInt -> Ptr Gio.IOStream -> Ptr () -> IO () socketEventCallbackWrapper _cb _ event connection _ = do let event' = (toEnum . fromIntegral) event connection' <- (newObject Gio.IOStream) connection _cb event' connection' onSocketEvent :: (GObject a, MonadIO m) => a -> SocketEventCallback -> m SignalHandlerId onSocketEvent obj cb = liftIO $ connectSocketEvent obj cb SignalConnectBefore afterSocketEvent :: (GObject a, MonadIO m) => a -> SocketEventCallback -> m SignalHandlerId afterSocketEvent obj cb = connectSocketEvent obj cb SignalConnectAfter connectSocketEvent :: (GObject a, MonadIO m) => a -> SocketEventCallback -> SignalConnectMode -> m SignalHandlerId connectSocketEvent obj cb after = liftIO $ do cb' <- mkSocketEventCallback (socketEventCallbackWrapper cb) connectSignalFunPtr obj "event" cb' after -- signal Socket::new-connection type SocketNewConnectionCallback = Socket -> IO () noSocketNewConnectionCallback :: Maybe SocketNewConnectionCallback noSocketNewConnectionCallback = Nothing type SocketNewConnectionCallbackC = Ptr () -> -- object Ptr Socket -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkSocketNewConnectionCallback :: SocketNewConnectionCallbackC -> IO (FunPtr SocketNewConnectionCallbackC) socketNewConnectionClosure :: SocketNewConnectionCallback -> IO Closure socketNewConnectionClosure cb = newCClosure =<< mkSocketNewConnectionCallback wrapped where wrapped = socketNewConnectionCallbackWrapper cb socketNewConnectionCallbackWrapper :: SocketNewConnectionCallback -> Ptr () -> Ptr Socket -> Ptr () -> IO () socketNewConnectionCallbackWrapper _cb _ new _ = do new' <- (newObject Socket) new _cb new' onSocketNewConnection :: (GObject a, MonadIO m) => a -> SocketNewConnectionCallback -> m SignalHandlerId onSocketNewConnection obj cb = liftIO $ connectSocketNewConnection obj cb SignalConnectBefore afterSocketNewConnection :: (GObject a, MonadIO m) => a -> SocketNewConnectionCallback -> m SignalHandlerId afterSocketNewConnection obj cb = connectSocketNewConnection obj cb SignalConnectAfter connectSocketNewConnection :: (GObject a, MonadIO m) => a -> SocketNewConnectionCallback -> SignalConnectMode -> m SignalHandlerId connectSocketNewConnection obj cb after = liftIO $ do cb' <- mkSocketNewConnectionCallback (socketNewConnectionCallbackWrapper cb) connectSignalFunPtr obj "new-connection" cb' after -- signal Socket::readable type SocketReadableCallback = IO () noSocketReadableCallback :: Maybe SocketReadableCallback noSocketReadableCallback = Nothing type SocketReadableCallbackC = Ptr () -> -- object Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkSocketReadableCallback :: SocketReadableCallbackC -> IO (FunPtr SocketReadableCallbackC) socketReadableClosure :: SocketReadableCallback -> IO Closure socketReadableClosure cb = newCClosure =<< mkSocketReadableCallback wrapped where wrapped = socketReadableCallbackWrapper cb socketReadableCallbackWrapper :: SocketReadableCallback -> Ptr () -> Ptr () -> IO () socketReadableCallbackWrapper _cb _ _ = do _cb onSocketReadable :: (GObject a, MonadIO m) => a -> SocketReadableCallback -> m SignalHandlerId onSocketReadable obj cb = liftIO $ connectSocketReadable obj cb SignalConnectBefore afterSocketReadable :: (GObject a, MonadIO m) => a -> SocketReadableCallback -> m SignalHandlerId afterSocketReadable obj cb = connectSocketReadable obj cb SignalConnectAfter connectSocketReadable :: (GObject a, MonadIO m) => a -> SocketReadableCallback -> SignalConnectMode -> m SignalHandlerId connectSocketReadable obj cb after = liftIO $ do cb' <- mkSocketReadableCallback (socketReadableCallbackWrapper cb) connectSignalFunPtr obj "readable" cb' after -- signal Socket::writable type SocketWritableCallback = IO () noSocketWritableCallback :: Maybe SocketWritableCallback noSocketWritableCallback = Nothing type SocketWritableCallbackC = Ptr () -> -- object Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkSocketWritableCallback :: SocketWritableCallbackC -> IO (FunPtr SocketWritableCallbackC) socketWritableClosure :: SocketWritableCallback -> IO Closure socketWritableClosure cb = newCClosure =<< mkSocketWritableCallback wrapped where wrapped = socketWritableCallbackWrapper cb socketWritableCallbackWrapper :: SocketWritableCallback -> Ptr () -> Ptr () -> IO () socketWritableCallbackWrapper _cb _ _ = do _cb onSocketWritable :: (GObject a, MonadIO m) => a -> SocketWritableCallback -> m SignalHandlerId onSocketWritable obj cb = liftIO $ connectSocketWritable obj cb SignalConnectBefore afterSocketWritable :: (GObject a, MonadIO m) => a -> SocketWritableCallback -> m SignalHandlerId afterSocketWritable obj cb = connectSocketWritable obj cb SignalConnectAfter connectSocketWritable :: (GObject a, MonadIO m) => a -> SocketWritableCallback -> SignalConnectMode -> m SignalHandlerId connectSocketWritable obj cb after = liftIO $ do cb' <- mkSocketWritableCallback (socketWritableCallbackWrapper cb) connectSignalFunPtr obj "writable" cb' after -- callback SocketCallback socketCallbackClosure :: SocketCallback -> IO Closure socketCallbackClosure cb = newCClosure =<< mkSocketCallback wrapped where wrapped = socketCallbackWrapper Nothing cb type SocketCallbackC = Ptr Socket -> Word32 -> Ptr () -> IO () foreign import ccall "wrapper" mkSocketCallback :: SocketCallbackC -> IO (FunPtr SocketCallbackC) type SocketCallback = Socket -> Word32 -> IO () noSocketCallback :: Maybe SocketCallback noSocketCallback = Nothing socketCallbackWrapper :: Maybe (Ptr (FunPtr (SocketCallbackC))) -> SocketCallback -> Ptr Socket -> Word32 -> Ptr () -> IO () socketCallbackWrapper funptrptr _cb sock status _ = do sock' <- (newObject Socket) sock _cb sock' status maybeReleaseFunPtr funptrptr -- Enum SocketIOStatus data SocketIOStatus = SocketIOStatusOk | SocketIOStatusWouldBlock | SocketIOStatusEof | SocketIOStatusError | AnotherSocketIOStatus Int deriving (Show, Eq) instance Enum SocketIOStatus where fromEnum SocketIOStatusOk = 0 fromEnum SocketIOStatusWouldBlock = 1 fromEnum SocketIOStatusEof = 2 fromEnum SocketIOStatusError = 3 fromEnum (AnotherSocketIOStatus k) = k toEnum 0 = SocketIOStatusOk toEnum 1 = SocketIOStatusWouldBlock toEnum 2 = SocketIOStatusEof toEnum 3 = SocketIOStatusError toEnum k = AnotherSocketIOStatus k foreign import ccall "soup_socket_io_status_get_type" c_soup_socket_io_status_get_type :: IO GType instance BoxedEnum SocketIOStatus where boxedEnumType _ = c_soup_socket_io_status_get_type -- Enum Status data Status = StatusNone | StatusCancelled | StatusCantResolve | StatusCantResolveProxy | StatusCantConnect | StatusCantConnectProxy | StatusSslFailed | StatusIoError | StatusMalformed | StatusTryAgain | StatusTooManyRedirects | StatusTlsFailed | StatusContinue | StatusSwitchingProtocols | StatusProcessing | StatusOk | StatusCreated | StatusAccepted | StatusNonAuthoritative | StatusNoContent | StatusResetContent | StatusPartialContent | StatusMultiStatus | StatusMultipleChoices | StatusMovedPermanently | StatusFound | StatusMovedTemporarily | StatusSeeOther | StatusNotModified | StatusUseProxy | StatusNotAppearingInThisProtocol | StatusTemporaryRedirect | StatusBadRequest | StatusUnauthorized | StatusPaymentRequired | StatusForbidden | StatusNotFound | StatusMethodNotAllowed | StatusNotAcceptable | StatusProxyAuthenticationRequired | StatusProxyUnauthorized | StatusRequestTimeout | StatusConflict | StatusGone | StatusLengthRequired | StatusPreconditionFailed | StatusRequestEntityTooLarge | StatusRequestUriTooLong | StatusUnsupportedMediaType | StatusRequestedRangeNotSatisfiable | StatusInvalidRange | StatusExpectationFailed | StatusUnprocessableEntity | StatusLocked | StatusFailedDependency | StatusInternalServerError | StatusNotImplemented | StatusBadGateway | StatusServiceUnavailable | StatusGatewayTimeout | StatusHttpVersionNotSupported | StatusInsufficientStorage | StatusNotExtended | AnotherStatus Int deriving (Show, Eq) instance Enum Status where fromEnum StatusNone = 0 fromEnum StatusCancelled = 1 fromEnum StatusCantResolve = 2 fromEnum StatusCantResolveProxy = 3 fromEnum StatusCantConnect = 4 fromEnum StatusCantConnectProxy = 5 fromEnum StatusSslFailed = 6 fromEnum StatusIoError = 7 fromEnum StatusMalformed = 8 fromEnum StatusTryAgain = 9 fromEnum StatusTooManyRedirects = 10 fromEnum StatusTlsFailed = 11 fromEnum StatusContinue = 100 fromEnum StatusSwitchingProtocols = 101 fromEnum StatusProcessing = 102 fromEnum StatusOk = 200 fromEnum StatusCreated = 201 fromEnum StatusAccepted = 202 fromEnum StatusNonAuthoritative = 203 fromEnum StatusNoContent = 204 fromEnum StatusResetContent = 205 fromEnum StatusPartialContent = 206 fromEnum StatusMultiStatus = 207 fromEnum StatusMultipleChoices = 300 fromEnum StatusMovedPermanently = 301 fromEnum StatusFound = 302 fromEnum StatusMovedTemporarily = 302 fromEnum StatusSeeOther = 303 fromEnum StatusNotModified = 304 fromEnum StatusUseProxy = 305 fromEnum StatusNotAppearingInThisProtocol = 306 fromEnum StatusTemporaryRedirect = 307 fromEnum StatusBadRequest = 400 fromEnum StatusUnauthorized = 401 fromEnum StatusPaymentRequired = 402 fromEnum StatusForbidden = 403 fromEnum StatusNotFound = 404 fromEnum StatusMethodNotAllowed = 405 fromEnum StatusNotAcceptable = 406 fromEnum StatusProxyAuthenticationRequired = 407 fromEnum StatusProxyUnauthorized = 407 fromEnum StatusRequestTimeout = 408 fromEnum StatusConflict = 409 fromEnum StatusGone = 410 fromEnum StatusLengthRequired = 411 fromEnum StatusPreconditionFailed = 412 fromEnum StatusRequestEntityTooLarge = 413 fromEnum StatusRequestUriTooLong = 414 fromEnum StatusUnsupportedMediaType = 415 fromEnum StatusRequestedRangeNotSatisfiable = 416 fromEnum StatusInvalidRange = 416 fromEnum StatusExpectationFailed = 417 fromEnum StatusUnprocessableEntity = 422 fromEnum StatusLocked = 423 fromEnum StatusFailedDependency = 424 fromEnum StatusInternalServerError = 500 fromEnum StatusNotImplemented = 501 fromEnum StatusBadGateway = 502 fromEnum StatusServiceUnavailable = 503 fromEnum StatusGatewayTimeout = 504 fromEnum StatusHttpVersionNotSupported = 505 fromEnum StatusInsufficientStorage = 507 fromEnum StatusNotExtended = 510 fromEnum (AnotherStatus k) = k toEnum 0 = StatusNone toEnum 1 = StatusCancelled toEnum 2 = StatusCantResolve toEnum 3 = StatusCantResolveProxy toEnum 4 = StatusCantConnect toEnum 5 = StatusCantConnectProxy toEnum 6 = StatusSslFailed toEnum 7 = StatusIoError toEnum 8 = StatusMalformed toEnum 9 = StatusTryAgain toEnum 10 = StatusTooManyRedirects toEnum 11 = StatusTlsFailed toEnum 100 = StatusContinue toEnum 101 = StatusSwitchingProtocols toEnum 102 = StatusProcessing toEnum 200 = StatusOk toEnum 201 = StatusCreated toEnum 202 = StatusAccepted toEnum 203 = StatusNonAuthoritative toEnum 204 = StatusNoContent toEnum 205 = StatusResetContent toEnum 206 = StatusPartialContent toEnum 207 = StatusMultiStatus toEnum 300 = StatusMultipleChoices toEnum 301 = StatusMovedPermanently toEnum 302 = StatusFound toEnum 303 = StatusSeeOther toEnum 304 = StatusNotModified toEnum 305 = StatusUseProxy toEnum 306 = StatusNotAppearingInThisProtocol toEnum 307 = StatusTemporaryRedirect toEnum 400 = StatusBadRequest toEnum 401 = StatusUnauthorized toEnum 402 = StatusPaymentRequired toEnum 403 = StatusForbidden toEnum 404 = StatusNotFound toEnum 405 = StatusMethodNotAllowed toEnum 406 = StatusNotAcceptable toEnum 407 = StatusProxyAuthenticationRequired toEnum 408 = StatusRequestTimeout toEnum 409 = StatusConflict toEnum 410 = StatusGone toEnum 411 = StatusLengthRequired toEnum 412 = StatusPreconditionFailed toEnum 413 = StatusRequestEntityTooLarge toEnum 414 = StatusRequestUriTooLong toEnum 415 = StatusUnsupportedMediaType toEnum 416 = StatusRequestedRangeNotSatisfiable toEnum 417 = StatusExpectationFailed toEnum 422 = StatusUnprocessableEntity toEnum 423 = StatusLocked toEnum 424 = StatusFailedDependency toEnum 500 = StatusInternalServerError toEnum 501 = StatusNotImplemented toEnum 502 = StatusBadGateway toEnum 503 = StatusServiceUnavailable toEnum 504 = StatusGatewayTimeout toEnum 505 = StatusHttpVersionNotSupported toEnum 507 = StatusInsufficientStorage toEnum 510 = StatusNotExtended toEnum k = AnotherStatus k foreign import ccall "soup_status_get_type" c_soup_status_get_type :: IO GType instance BoxedEnum Status where boxedEnumType _ = c_soup_status_get_type -- Enum TLDError data TLDError = TLDErrorInvalidHostname | TLDErrorIsIpAddress | TLDErrorNotEnoughDomains | TLDErrorNoBaseDomain | AnotherTLDError Int deriving (Show, Eq) instance Enum TLDError where fromEnum TLDErrorInvalidHostname = 0 fromEnum TLDErrorIsIpAddress = 1 fromEnum TLDErrorNotEnoughDomains = 2 fromEnum TLDErrorNoBaseDomain = 3 fromEnum (AnotherTLDError k) = k toEnum 0 = TLDErrorInvalidHostname toEnum 1 = TLDErrorIsIpAddress toEnum 2 = TLDErrorNotEnoughDomains toEnum 3 = TLDErrorNoBaseDomain toEnum k = AnotherTLDError k instance GErrorClass TLDError where gerrorClassDomain _ = "soup_tld_error_quark" catchTLDError :: IO a -> (TLDError -> GErrorMessage -> IO a) -> IO a catchTLDError = catchGErrorJustDomain handleTLDError :: (TLDError -> GErrorMessage -> IO a) -> IO a -> IO a handleTLDError = handleGErrorJustDomain foreign import ccall "soup_tld_error_get_type" c_soup_tld_error_get_type :: IO GType instance BoxedEnum TLDError where boxedEnumType _ = c_soup_tld_error_get_type -- struct URI newtype URI = URI (ForeignPtr URI) noURI :: Maybe URI noURI = Nothing foreign import ccall "soup_uri_get_type" c_soup_uri_get_type :: IO GType instance BoxedObject URI where boxedType _ = c_soup_uri_get_type uRIReadScheme :: URI -> IO T.Text uRIReadScheme s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 0) :: IO CString val' <- cstringToText val return val' uRIReadUser :: URI -> IO T.Text uRIReadUser s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 8) :: IO CString val' <- cstringToText val return val' uRIReadPassword :: URI -> IO T.Text uRIReadPassword s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 16) :: IO CString val' <- cstringToText val return val' uRIReadHost :: URI -> IO T.Text uRIReadHost s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 24) :: IO CString val' <- cstringToText val return val' uRIReadPort :: URI -> IO Word32 uRIReadPort s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 32) :: IO Word32 return val uRIReadPath :: URI -> IO T.Text uRIReadPath s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 40) :: IO CString val' <- cstringToText val return val' uRIReadQuery :: URI -> IO T.Text uRIReadQuery s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 48) :: IO CString val' <- cstringToText val return val' uRIReadFragment :: URI -> IO T.Text uRIReadFragment s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 56) :: IO CString val' <- cstringToText val return val' -- method URI::new -- method type : Constructor -- Args : [Arg {argName = "uri_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "uri_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "URI" -- throws : False -- Skip return : False foreign import ccall "soup_uri_new" soup_uri_new :: CString -> -- uri_string : TBasicType TUTF8 IO (Ptr URI) uRINew :: (MonadIO m) => Maybe (T.Text) -> -- uri_string m URI uRINew uri_string = liftIO $ do maybeUri_string <- case uri_string of Nothing -> return nullPtr Just jUri_string -> do jUri_string' <- textToCString jUri_string return jUri_string' result <- soup_uri_new maybeUri_string checkUnexpectedReturnNULL "soup_uri_new" result result' <- (wrapBoxed URI) result freeMem maybeUri_string return result' -- method URI::copy -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "URI" -- throws : False -- Skip return : False foreign import ccall "soup_uri_copy" soup_uri_copy :: Ptr URI -> -- _obj : TInterface "Soup" "URI" IO (Ptr URI) uRICopy :: (MonadIO m) => URI -> -- _obj m URI uRICopy _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_uri_copy _obj' checkUnexpectedReturnNULL "soup_uri_copy" result result' <- (wrapBoxed URI) result touchManagedPtr _obj return result' -- method URI::copy_host -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "URI" -- throws : False -- Skip return : False foreign import ccall "soup_uri_copy_host" soup_uri_copy_host :: Ptr URI -> -- _obj : TInterface "Soup" "URI" IO (Ptr URI) uRICopyHost :: (MonadIO m) => URI -> -- _obj m URI uRICopyHost _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_uri_copy_host _obj' checkUnexpectedReturnNULL "soup_uri_copy_host" result result' <- (wrapBoxed URI) result touchManagedPtr _obj return result' -- method URI::equal -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri2", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri2", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_uri_equal" soup_uri_equal :: Ptr URI -> -- _obj : TInterface "Soup" "URI" Ptr URI -> -- uri2 : TInterface "Soup" "URI" IO CInt uRIEqual :: (MonadIO m) => URI -> -- _obj URI -> -- uri2 m Bool uRIEqual _obj uri2 = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj let uri2' = unsafeManagedPtrGetPtr uri2 result <- soup_uri_equal _obj' uri2' let result' = (/= 0) result touchManagedPtr _obj touchManagedPtr uri2 return result' -- method URI::free -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_uri_free" soup_uri_free :: Ptr URI -> -- _obj : TInterface "Soup" "URI" IO () uRIFree :: (MonadIO m) => URI -> -- _obj m () uRIFree _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj soup_uri_free _obj' touchManagedPtr _obj return () -- method URI::get_fragment -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_uri_get_fragment" soup_uri_get_fragment :: Ptr URI -> -- _obj : TInterface "Soup" "URI" IO CString uRIGetFragment :: (MonadIO m) => URI -> -- _obj m T.Text uRIGetFragment _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_uri_get_fragment _obj' checkUnexpectedReturnNULL "soup_uri_get_fragment" result result' <- cstringToText result touchManagedPtr _obj return result' -- method URI::get_host -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_uri_get_host" soup_uri_get_host :: Ptr URI -> -- _obj : TInterface "Soup" "URI" IO CString uRIGetHost :: (MonadIO m) => URI -> -- _obj m T.Text uRIGetHost _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_uri_get_host _obj' checkUnexpectedReturnNULL "soup_uri_get_host" result result' <- cstringToText result touchManagedPtr _obj return result' -- method URI::get_password -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_uri_get_password" soup_uri_get_password :: Ptr URI -> -- _obj : TInterface "Soup" "URI" IO CString uRIGetPassword :: (MonadIO m) => URI -> -- _obj m T.Text uRIGetPassword _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_uri_get_password _obj' checkUnexpectedReturnNULL "soup_uri_get_password" result result' <- cstringToText result touchManagedPtr _obj return result' -- method URI::get_path -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_uri_get_path" soup_uri_get_path :: Ptr URI -> -- _obj : TInterface "Soup" "URI" IO CString uRIGetPath :: (MonadIO m) => URI -> -- _obj m T.Text uRIGetPath _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_uri_get_path _obj' checkUnexpectedReturnNULL "soup_uri_get_path" result result' <- cstringToText result touchManagedPtr _obj return result' -- method URI::get_port -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_uri_get_port" soup_uri_get_port :: Ptr URI -> -- _obj : TInterface "Soup" "URI" IO Word32 uRIGetPort :: (MonadIO m) => URI -> -- _obj m Word32 uRIGetPort _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_uri_get_port _obj' touchManagedPtr _obj return result -- method URI::get_query -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_uri_get_query" soup_uri_get_query :: Ptr URI -> -- _obj : TInterface "Soup" "URI" IO CString uRIGetQuery :: (MonadIO m) => URI -> -- _obj m T.Text uRIGetQuery _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_uri_get_query _obj' checkUnexpectedReturnNULL "soup_uri_get_query" result result' <- cstringToText result touchManagedPtr _obj return result' -- method URI::get_scheme -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_uri_get_scheme" soup_uri_get_scheme :: Ptr URI -> -- _obj : TInterface "Soup" "URI" IO CString uRIGetScheme :: (MonadIO m) => URI -> -- _obj m T.Text uRIGetScheme _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_uri_get_scheme _obj' checkUnexpectedReturnNULL "soup_uri_get_scheme" result result' <- cstringToText result touchManagedPtr _obj return result' -- method URI::get_user -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_uri_get_user" soup_uri_get_user :: Ptr URI -> -- _obj : TInterface "Soup" "URI" IO CString uRIGetUser :: (MonadIO m) => URI -> -- _obj m T.Text uRIGetUser _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_uri_get_user _obj' checkUnexpectedReturnNULL "soup_uri_get_user" result result' <- cstringToText result touchManagedPtr _obj return result' -- method URI::host_equal -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "v2", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "v2", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_uri_host_equal" soup_uri_host_equal :: Ptr URI -> -- _obj : TInterface "Soup" "URI" Ptr URI -> -- v2 : TInterface "Soup" "URI" IO CInt uRIHostEqual :: (MonadIO m) => URI -> -- _obj URI -> -- v2 m Bool uRIHostEqual _obj v2 = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj let v2' = unsafeManagedPtrGetPtr v2 result <- soup_uri_host_equal _obj' v2' let result' = (/= 0) result touchManagedPtr _obj touchManagedPtr v2 return result' -- method URI::host_hash -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_uri_host_hash" soup_uri_host_hash :: Ptr URI -> -- _obj : TInterface "Soup" "URI" IO Word32 uRIHostHash :: (MonadIO m) => URI -> -- _obj m Word32 uRIHostHash _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_uri_host_hash _obj' touchManagedPtr _obj return result -- method URI::new_with_base -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "URI" -- throws : False -- Skip return : False foreign import ccall "soup_uri_new_with_base" soup_uri_new_with_base :: Ptr URI -> -- _obj : TInterface "Soup" "URI" CString -> -- uri_string : TBasicType TUTF8 IO (Ptr URI) uRINewWithBase :: (MonadIO m) => URI -> -- _obj T.Text -> -- uri_string m URI uRINewWithBase _obj uri_string = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj uri_string' <- textToCString uri_string result <- soup_uri_new_with_base _obj' uri_string' checkUnexpectedReturnNULL "soup_uri_new_with_base" result result' <- (wrapBoxed URI) result touchManagedPtr _obj freeMem uri_string' return result' -- method URI::set_fragment -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "fragment", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "fragment", argType = 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_uri_set_fragment" soup_uri_set_fragment :: Ptr URI -> -- _obj : TInterface "Soup" "URI" CString -> -- fragment : TBasicType TUTF8 IO () uRISetFragment :: (MonadIO m) => URI -> -- _obj Maybe (T.Text) -> -- fragment m () uRISetFragment _obj fragment = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj maybeFragment <- case fragment of Nothing -> return nullPtr Just jFragment -> do jFragment' <- textToCString jFragment return jFragment' soup_uri_set_fragment _obj' maybeFragment touchManagedPtr _obj freeMem maybeFragment return () -- method URI::set_host -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "host", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "host", argType = 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_uri_set_host" soup_uri_set_host :: Ptr URI -> -- _obj : TInterface "Soup" "URI" CString -> -- host : TBasicType TUTF8 IO () uRISetHost :: (MonadIO m) => URI -> -- _obj Maybe (T.Text) -> -- host m () uRISetHost _obj host = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj maybeHost <- case host of Nothing -> return nullPtr Just jHost -> do jHost' <- textToCString jHost return jHost' soup_uri_set_host _obj' maybeHost touchManagedPtr _obj freeMem maybeHost return () -- method URI::set_password -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "password", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "password", argType = 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_uri_set_password" soup_uri_set_password :: Ptr URI -> -- _obj : TInterface "Soup" "URI" CString -> -- password : TBasicType TUTF8 IO () uRISetPassword :: (MonadIO m) => URI -> -- _obj Maybe (T.Text) -> -- password m () uRISetPassword _obj password = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj maybePassword <- case password of Nothing -> return nullPtr Just jPassword -> do jPassword' <- textToCString jPassword return jPassword' soup_uri_set_password _obj' maybePassword touchManagedPtr _obj freeMem maybePassword return () -- method URI::set_path -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", 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_uri_set_path" soup_uri_set_path :: Ptr URI -> -- _obj : TInterface "Soup" "URI" CString -> -- path : TBasicType TUTF8 IO () uRISetPath :: (MonadIO m) => URI -> -- _obj T.Text -> -- path m () uRISetPath _obj path = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj path' <- textToCString path soup_uri_set_path _obj' path' touchManagedPtr _obj freeMem path' return () -- method URI::set_port -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "port", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "port", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_uri_set_port" soup_uri_set_port :: Ptr URI -> -- _obj : TInterface "Soup" "URI" Word32 -> -- port : TBasicType TUInt32 IO () uRISetPort :: (MonadIO m) => URI -> -- _obj Word32 -> -- port m () uRISetPort _obj port = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj soup_uri_set_port _obj' port touchManagedPtr _obj return () -- method URI::set_query -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "query", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "query", argType = 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_uri_set_query" soup_uri_set_query :: Ptr URI -> -- _obj : TInterface "Soup" "URI" CString -> -- query : TBasicType TUTF8 IO () uRISetQuery :: (MonadIO m) => URI -> -- _obj Maybe (T.Text) -> -- query m () uRISetQuery _obj query = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj maybeQuery <- case query of Nothing -> return nullPtr Just jQuery -> do jQuery' <- textToCString jQuery return jQuery' soup_uri_set_query _obj' maybeQuery touchManagedPtr _obj freeMem maybeQuery return () -- method URI::set_query_from_form -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "form", argType = TGHash (TBasicType TUTF8) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "form", argType = TGHash (TBasicType TUTF8) (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_uri_set_query_from_form" soup_uri_set_query_from_form :: Ptr URI -> -- _obj : TInterface "Soup" "URI" Ptr (GHashTable CString CString) -> -- form : TGHash (TBasicType TUTF8) (TBasicType TUTF8) IO () uRISetQueryFromForm :: (MonadIO m) => URI -> -- _obj Map.Map T.Text T.Text -> -- form m () uRISetQueryFromForm _obj form = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj let form' = Map.toList form form'' <- mapFirstA textToCString form' form''' <- mapSecondA textToCString form'' let form'''' = mapFirst cstringPackPtr form''' let form''''' = mapSecond cstringPackPtr form'''' form'''''' <- packGHashTable gStrHash gStrEqual (Just ptr_to_g_free) (Just ptr_to_g_free) form''''' soup_uri_set_query_from_form _obj' form'''''' touchManagedPtr _obj unrefGHashTable form'''''' return () -- method URI::set_scheme -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "scheme", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "scheme", 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_uri_set_scheme" soup_uri_set_scheme :: Ptr URI -> -- _obj : TInterface "Soup" "URI" CString -> -- scheme : TBasicType TUTF8 IO () uRISetScheme :: (MonadIO m) => URI -> -- _obj T.Text -> -- scheme m () uRISetScheme _obj scheme = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj scheme' <- textToCString scheme soup_uri_set_scheme _obj' scheme' touchManagedPtr _obj freeMem scheme' return () -- method URI::set_user -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user", argType = 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_uri_set_user" soup_uri_set_user :: Ptr URI -> -- _obj : TInterface "Soup" "URI" CString -> -- user : TBasicType TUTF8 IO () uRISetUser :: (MonadIO m) => URI -> -- _obj Maybe (T.Text) -> -- user m () uRISetUser _obj user = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj maybeUser <- case user of Nothing -> return nullPtr Just jUser -> do jUser' <- textToCString jUser return jUser' soup_uri_set_user _obj' maybeUser touchManagedPtr _obj freeMem maybeUser return () -- method URI::to_string -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "just_path_and_query", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "just_path_and_query", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_uri_to_string" soup_uri_to_string :: Ptr URI -> -- _obj : TInterface "Soup" "URI" CInt -> -- just_path_and_query : TBasicType TBoolean IO CString uRIToString :: (MonadIO m) => URI -> -- _obj Bool -> -- just_path_and_query m T.Text uRIToString _obj just_path_and_query = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj let just_path_and_query' = (fromIntegral . fromEnum) just_path_and_query result <- soup_uri_to_string _obj' just_path_and_query' checkUnexpectedReturnNULL "soup_uri_to_string" result result' <- cstringToText result freeMem result touchManagedPtr _obj return result' -- method URI::uses_default_port -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_uri_uses_default_port" soup_uri_uses_default_port :: Ptr URI -> -- _obj : TInterface "Soup" "URI" IO CInt uRIUsesDefaultPort :: (MonadIO m) => URI -> -- _obj m Bool uRIUsesDefaultPort _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj result <- soup_uri_uses_default_port _obj' let result' = (/= 0) result touchManagedPtr _obj return result' -- Enum WebsocketCloseCode data WebsocketCloseCode = WebsocketCloseCodeNormal | WebsocketCloseCodeGoingAway | WebsocketCloseCodeProtocolError | WebsocketCloseCodeUnsupportedData | WebsocketCloseCodeNoStatus | WebsocketCloseCodeAbnormal | WebsocketCloseCodeBadData | WebsocketCloseCodePolicyViolation | WebsocketCloseCodeTooBig | WebsocketCloseCodeNoExtension | WebsocketCloseCodeServerError | WebsocketCloseCodeTlsHandshake | AnotherWebsocketCloseCode Int deriving (Show, Eq) instance Enum WebsocketCloseCode where fromEnum WebsocketCloseCodeNormal = 1000 fromEnum WebsocketCloseCodeGoingAway = 1001 fromEnum WebsocketCloseCodeProtocolError = 1002 fromEnum WebsocketCloseCodeUnsupportedData = 1003 fromEnum WebsocketCloseCodeNoStatus = 1005 fromEnum WebsocketCloseCodeAbnormal = 1006 fromEnum WebsocketCloseCodeBadData = 1007 fromEnum WebsocketCloseCodePolicyViolation = 1008 fromEnum WebsocketCloseCodeTooBig = 1009 fromEnum WebsocketCloseCodeNoExtension = 1010 fromEnum WebsocketCloseCodeServerError = 1011 fromEnum WebsocketCloseCodeTlsHandshake = 1015 fromEnum (AnotherWebsocketCloseCode k) = k toEnum 1000 = WebsocketCloseCodeNormal toEnum 1001 = WebsocketCloseCodeGoingAway toEnum 1002 = WebsocketCloseCodeProtocolError toEnum 1003 = WebsocketCloseCodeUnsupportedData toEnum 1005 = WebsocketCloseCodeNoStatus toEnum 1006 = WebsocketCloseCodeAbnormal toEnum 1007 = WebsocketCloseCodeBadData toEnum 1008 = WebsocketCloseCodePolicyViolation toEnum 1009 = WebsocketCloseCodeTooBig toEnum 1010 = WebsocketCloseCodeNoExtension toEnum 1011 = WebsocketCloseCodeServerError toEnum 1015 = WebsocketCloseCodeTlsHandshake toEnum k = AnotherWebsocketCloseCode k foreign import ccall "soup_websocket_close_code_get_type" c_soup_websocket_close_code_get_type :: IO GType instance BoxedEnum WebsocketCloseCode where boxedEnumType _ = c_soup_websocket_close_code_get_type -- object WebsocketConnection newtype WebsocketConnection = WebsocketConnection (ForeignPtr WebsocketConnection) noWebsocketConnection :: Maybe WebsocketConnection noWebsocketConnection = Nothing foreign import ccall "soup_websocket_connection_get_type" c_soup_websocket_connection_get_type :: IO GType type instance ParentTypes WebsocketConnection = '[GObject.Object] instance GObject WebsocketConnection where gobjectIsInitiallyUnowned _ = False gobjectType _ = c_soup_websocket_connection_get_type class GObject o => WebsocketConnectionK o instance (GObject o, IsDescendantOf WebsocketConnection o) => WebsocketConnectionK o toWebsocketConnection :: WebsocketConnectionK o => o -> IO WebsocketConnection toWebsocketConnection = unsafeCastTo WebsocketConnection -- method WebsocketConnection::new -- method type : Constructor -- Args : [Arg {argName = "stream", argType = TInterface "Gio" "IOStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type", argType = TInterface "Soup" "WebsocketConnectionType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "origin", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "protocol", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "stream", argType = TInterface "Gio" "IOStream", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type", argType = TInterface "Soup" "WebsocketConnectionType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "origin", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "protocol", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "WebsocketConnection" -- throws : False -- Skip return : False foreign import ccall "soup_websocket_connection_new" soup_websocket_connection_new :: Ptr Gio.IOStream -> -- stream : TInterface "Gio" "IOStream" Ptr URI -> -- uri : TInterface "Soup" "URI" CUInt -> -- type : TInterface "Soup" "WebsocketConnectionType" CString -> -- origin : TBasicType TUTF8 CString -> -- protocol : TBasicType TUTF8 IO (Ptr WebsocketConnection) websocketConnectionNew :: (MonadIO m, Gio.IOStreamK a) => a -> -- stream URI -> -- uri WebsocketConnectionType -> -- type Maybe (T.Text) -> -- origin Maybe (T.Text) -> -- protocol m WebsocketConnection websocketConnectionNew stream uri type_ origin protocol = liftIO $ do let stream' = unsafeManagedPtrCastPtr stream let uri' = unsafeManagedPtrGetPtr uri let type_' = (fromIntegral . fromEnum) type_ maybeOrigin <- case origin of Nothing -> return nullPtr Just jOrigin -> do jOrigin' <- textToCString jOrigin return jOrigin' maybeProtocol <- case protocol of Nothing -> return nullPtr Just jProtocol -> do jProtocol' <- textToCString jProtocol return jProtocol' result <- soup_websocket_connection_new stream' uri' type_' maybeOrigin maybeProtocol checkUnexpectedReturnNULL "soup_websocket_connection_new" result result' <- (wrapObject WebsocketConnection) result touchManagedPtr stream touchManagedPtr uri freeMem maybeOrigin freeMem maybeProtocol return result' -- method WebsocketConnection::close -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "code", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "code", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = 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_websocket_connection_close" soup_websocket_connection_close :: Ptr WebsocketConnection -> -- _obj : TInterface "Soup" "WebsocketConnection" Word16 -> -- code : TBasicType TUInt16 CString -> -- data : TBasicType TUTF8 IO () websocketConnectionClose :: (MonadIO m, WebsocketConnectionK a) => a -> -- _obj Word16 -> -- code Maybe (T.Text) -> -- data m () websocketConnectionClose _obj code data_ = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj maybeData_ <- case data_ of Nothing -> return nullPtr Just jData_ -> do jData_' <- textToCString jData_ return jData_' soup_websocket_connection_close _obj' code maybeData_ touchManagedPtr _obj freeMem maybeData_ return () -- method WebsocketConnection::get_close_code -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUInt16 -- throws : False -- Skip return : False foreign import ccall "soup_websocket_connection_get_close_code" soup_websocket_connection_get_close_code :: Ptr WebsocketConnection -> -- _obj : TInterface "Soup" "WebsocketConnection" IO Word16 websocketConnectionGetCloseCode :: (MonadIO m, WebsocketConnectionK a) => a -> -- _obj m Word16 websocketConnectionGetCloseCode _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_websocket_connection_get_close_code _obj' touchManagedPtr _obj return result -- method WebsocketConnection::get_close_data -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_websocket_connection_get_close_data" soup_websocket_connection_get_close_data :: Ptr WebsocketConnection -> -- _obj : TInterface "Soup" "WebsocketConnection" IO CString websocketConnectionGetCloseData :: (MonadIO m, WebsocketConnectionK a) => a -> -- _obj m T.Text websocketConnectionGetCloseData _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_websocket_connection_get_close_data _obj' checkUnexpectedReturnNULL "soup_websocket_connection_get_close_data" result result' <- cstringToText result touchManagedPtr _obj return result' -- method WebsocketConnection::get_connection_type -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "WebsocketConnectionType" -- throws : False -- Skip return : False foreign import ccall "soup_websocket_connection_get_connection_type" soup_websocket_connection_get_connection_type :: Ptr WebsocketConnection -> -- _obj : TInterface "Soup" "WebsocketConnection" IO CUInt websocketConnectionGetConnectionType :: (MonadIO m, WebsocketConnectionK a) => a -> -- _obj m WebsocketConnectionType websocketConnectionGetConnectionType _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_websocket_connection_get_connection_type _obj' let result' = (toEnum . fromIntegral) result touchManagedPtr _obj return result' -- method WebsocketConnection::get_io_stream -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Gio" "IOStream" -- throws : False -- Skip return : False foreign import ccall "soup_websocket_connection_get_io_stream" soup_websocket_connection_get_io_stream :: Ptr WebsocketConnection -> -- _obj : TInterface "Soup" "WebsocketConnection" IO (Ptr Gio.IOStream) websocketConnectionGetIoStream :: (MonadIO m, WebsocketConnectionK a) => a -> -- _obj m Gio.IOStream websocketConnectionGetIoStream _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_websocket_connection_get_io_stream _obj' checkUnexpectedReturnNULL "soup_websocket_connection_get_io_stream" result result' <- (newObject Gio.IOStream) result touchManagedPtr _obj return result' -- method WebsocketConnection::get_origin -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_websocket_connection_get_origin" soup_websocket_connection_get_origin :: Ptr WebsocketConnection -> -- _obj : TInterface "Soup" "WebsocketConnection" IO CString websocketConnectionGetOrigin :: (MonadIO m, WebsocketConnectionK a) => a -> -- _obj m T.Text websocketConnectionGetOrigin _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_websocket_connection_get_origin _obj' checkUnexpectedReturnNULL "soup_websocket_connection_get_origin" result result' <- cstringToText result touchManagedPtr _obj return result' -- method WebsocketConnection::get_protocol -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_websocket_connection_get_protocol" soup_websocket_connection_get_protocol :: Ptr WebsocketConnection -> -- _obj : TInterface "Soup" "WebsocketConnection" IO CString websocketConnectionGetProtocol :: (MonadIO m, WebsocketConnectionK a) => a -> -- _obj m T.Text websocketConnectionGetProtocol _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_websocket_connection_get_protocol _obj' checkUnexpectedReturnNULL "soup_websocket_connection_get_protocol" result result' <- cstringToText result touchManagedPtr _obj return result' -- method WebsocketConnection::get_state -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "WebsocketState" -- throws : False -- Skip return : False foreign import ccall "soup_websocket_connection_get_state" soup_websocket_connection_get_state :: Ptr WebsocketConnection -> -- _obj : TInterface "Soup" "WebsocketConnection" IO CUInt websocketConnectionGetState :: (MonadIO m, WebsocketConnectionK a) => a -> -- _obj m WebsocketState websocketConnectionGetState _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_websocket_connection_get_state _obj' let result' = (toEnum . fromIntegral) result touchManagedPtr _obj return result' -- method WebsocketConnection::get_uri -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "URI" -- throws : False -- Skip return : False foreign import ccall "soup_websocket_connection_get_uri" soup_websocket_connection_get_uri :: Ptr WebsocketConnection -> -- _obj : TInterface "Soup" "WebsocketConnection" IO (Ptr URI) websocketConnectionGetUri :: (MonadIO m, WebsocketConnectionK a) => a -> -- _obj m URI websocketConnectionGetUri _obj = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj result <- soup_websocket_connection_get_uri _obj' checkUnexpectedReturnNULL "soup_websocket_connection_get_uri" result result' <- (newBoxed URI) result touchManagedPtr _obj return result' -- method WebsocketConnection::send_binary -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_websocket_connection_send_binary" soup_websocket_connection_send_binary :: Ptr WebsocketConnection -> -- _obj : TInterface "Soup" "WebsocketConnection" Ptr Word8 -> -- data : TCArray False (-1) 2 (TBasicType TUInt8) Word64 -> -- length : TBasicType TUInt64 IO () websocketConnectionSendBinary :: (MonadIO m, WebsocketConnectionK a) => a -> -- _obj ByteString -> -- data m () websocketConnectionSendBinary _obj data_ = liftIO $ do let length_ = fromIntegral $ B.length data_ let _obj' = unsafeManagedPtrCastPtr _obj data_' <- packByteString data_ soup_websocket_connection_send_binary _obj' data_' length_ touchManagedPtr _obj freeMem data_' return () -- method WebsocketConnection::send_text -- method type : OrdinaryMethod -- Args : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "text", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "_obj", argType = TInterface "Soup" "WebsocketConnection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "text", 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_websocket_connection_send_text" soup_websocket_connection_send_text :: Ptr WebsocketConnection -> -- _obj : TInterface "Soup" "WebsocketConnection" CString -> -- text : TBasicType TUTF8 IO () websocketConnectionSendText :: (MonadIO m, WebsocketConnectionK a) => a -> -- _obj T.Text -> -- text m () websocketConnectionSendText _obj text = liftIO $ do let _obj' = unsafeManagedPtrCastPtr _obj text' <- textToCString text soup_websocket_connection_send_text _obj' text' touchManagedPtr _obj freeMem text' return () -- signal WebsocketConnection::closed type WebsocketConnectionClosedCallback = IO () noWebsocketConnectionClosedCallback :: Maybe WebsocketConnectionClosedCallback noWebsocketConnectionClosedCallback = Nothing type WebsocketConnectionClosedCallbackC = Ptr () -> -- object Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkWebsocketConnectionClosedCallback :: WebsocketConnectionClosedCallbackC -> IO (FunPtr WebsocketConnectionClosedCallbackC) websocketConnectionClosedClosure :: WebsocketConnectionClosedCallback -> IO Closure websocketConnectionClosedClosure cb = newCClosure =<< mkWebsocketConnectionClosedCallback wrapped where wrapped = websocketConnectionClosedCallbackWrapper cb websocketConnectionClosedCallbackWrapper :: WebsocketConnectionClosedCallback -> Ptr () -> Ptr () -> IO () websocketConnectionClosedCallbackWrapper _cb _ _ = do _cb onWebsocketConnectionClosed :: (GObject a, MonadIO m) => a -> WebsocketConnectionClosedCallback -> m SignalHandlerId onWebsocketConnectionClosed obj cb = liftIO $ connectWebsocketConnectionClosed obj cb SignalConnectBefore afterWebsocketConnectionClosed :: (GObject a, MonadIO m) => a -> WebsocketConnectionClosedCallback -> m SignalHandlerId afterWebsocketConnectionClosed obj cb = connectWebsocketConnectionClosed obj cb SignalConnectAfter connectWebsocketConnectionClosed :: (GObject a, MonadIO m) => a -> WebsocketConnectionClosedCallback -> SignalConnectMode -> m SignalHandlerId connectWebsocketConnectionClosed obj cb after = liftIO $ do cb' <- mkWebsocketConnectionClosedCallback (websocketConnectionClosedCallbackWrapper cb) connectSignalFunPtr obj "closed" cb' after -- signal WebsocketConnection::closing type WebsocketConnectionClosingCallback = IO () noWebsocketConnectionClosingCallback :: Maybe WebsocketConnectionClosingCallback noWebsocketConnectionClosingCallback = Nothing type WebsocketConnectionClosingCallbackC = Ptr () -> -- object Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkWebsocketConnectionClosingCallback :: WebsocketConnectionClosingCallbackC -> IO (FunPtr WebsocketConnectionClosingCallbackC) websocketConnectionClosingClosure :: WebsocketConnectionClosingCallback -> IO Closure websocketConnectionClosingClosure cb = newCClosure =<< mkWebsocketConnectionClosingCallback wrapped where wrapped = websocketConnectionClosingCallbackWrapper cb websocketConnectionClosingCallbackWrapper :: WebsocketConnectionClosingCallback -> Ptr () -> Ptr () -> IO () websocketConnectionClosingCallbackWrapper _cb _ _ = do _cb onWebsocketConnectionClosing :: (GObject a, MonadIO m) => a -> WebsocketConnectionClosingCallback -> m SignalHandlerId onWebsocketConnectionClosing obj cb = liftIO $ connectWebsocketConnectionClosing obj cb SignalConnectBefore afterWebsocketConnectionClosing :: (GObject a, MonadIO m) => a -> WebsocketConnectionClosingCallback -> m SignalHandlerId afterWebsocketConnectionClosing obj cb = connectWebsocketConnectionClosing obj cb SignalConnectAfter connectWebsocketConnectionClosing :: (GObject a, MonadIO m) => a -> WebsocketConnectionClosingCallback -> SignalConnectMode -> m SignalHandlerId connectWebsocketConnectionClosing obj cb after = liftIO $ do cb' <- mkWebsocketConnectionClosingCallback (websocketConnectionClosingCallbackWrapper cb) connectSignalFunPtr obj "closing" cb' after -- signal WebsocketConnection::error type WebsocketConnectionErrorCallback = GError -> IO () noWebsocketConnectionErrorCallback :: Maybe WebsocketConnectionErrorCallback noWebsocketConnectionErrorCallback = Nothing type WebsocketConnectionErrorCallbackC = Ptr () -> -- object Ptr GError -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkWebsocketConnectionErrorCallback :: WebsocketConnectionErrorCallbackC -> IO (FunPtr WebsocketConnectionErrorCallbackC) websocketConnectionErrorClosure :: WebsocketConnectionErrorCallback -> IO Closure websocketConnectionErrorClosure cb = newCClosure =<< mkWebsocketConnectionErrorCallback wrapped where wrapped = websocketConnectionErrorCallbackWrapper cb websocketConnectionErrorCallbackWrapper :: WebsocketConnectionErrorCallback -> Ptr () -> Ptr GError -> Ptr () -> IO () websocketConnectionErrorCallbackWrapper _cb _ error_ _ = do error_' <- (newBoxed GError) error_ _cb error_' onWebsocketConnectionError :: (GObject a, MonadIO m) => a -> WebsocketConnectionErrorCallback -> m SignalHandlerId onWebsocketConnectionError obj cb = liftIO $ connectWebsocketConnectionError obj cb SignalConnectBefore afterWebsocketConnectionError :: (GObject a, MonadIO m) => a -> WebsocketConnectionErrorCallback -> m SignalHandlerId afterWebsocketConnectionError obj cb = connectWebsocketConnectionError obj cb SignalConnectAfter connectWebsocketConnectionError :: (GObject a, MonadIO m) => a -> WebsocketConnectionErrorCallback -> SignalConnectMode -> m SignalHandlerId connectWebsocketConnectionError obj cb after = liftIO $ do cb' <- mkWebsocketConnectionErrorCallback (websocketConnectionErrorCallbackWrapper cb) connectSignalFunPtr obj "error" cb' after -- signal WebsocketConnection::message type WebsocketConnectionMessageCallback = Int32 -> GLib.Bytes -> IO () noWebsocketConnectionMessageCallback :: Maybe WebsocketConnectionMessageCallback noWebsocketConnectionMessageCallback = Nothing type WebsocketConnectionMessageCallbackC = Ptr () -> -- object Int32 -> Ptr GLib.Bytes -> Ptr () -> -- user_data IO () foreign import ccall "wrapper" mkWebsocketConnectionMessageCallback :: WebsocketConnectionMessageCallbackC -> IO (FunPtr WebsocketConnectionMessageCallbackC) websocketConnectionMessageClosure :: WebsocketConnectionMessageCallback -> IO Closure websocketConnectionMessageClosure cb = newCClosure =<< mkWebsocketConnectionMessageCallback wrapped where wrapped = websocketConnectionMessageCallbackWrapper cb websocketConnectionMessageCallbackWrapper :: WebsocketConnectionMessageCallback -> Ptr () -> Int32 -> Ptr GLib.Bytes -> Ptr () -> IO () websocketConnectionMessageCallbackWrapper _cb _ type_ message _ = do message' <- (newBoxed GLib.Bytes) message _cb type_ message' onWebsocketConnectionMessage :: (GObject a, MonadIO m) => a -> WebsocketConnectionMessageCallback -> m SignalHandlerId onWebsocketConnectionMessage obj cb = liftIO $ connectWebsocketConnectionMessage obj cb SignalConnectBefore afterWebsocketConnectionMessage :: (GObject a, MonadIO m) => a -> WebsocketConnectionMessageCallback -> m SignalHandlerId afterWebsocketConnectionMessage obj cb = connectWebsocketConnectionMessage obj cb SignalConnectAfter connectWebsocketConnectionMessage :: (GObject a, MonadIO m) => a -> WebsocketConnectionMessageCallback -> SignalConnectMode -> m SignalHandlerId connectWebsocketConnectionMessage obj cb after = liftIO $ do cb' <- mkWebsocketConnectionMessageCallback (websocketConnectionMessageCallbackWrapper cb) connectSignalFunPtr obj "message" cb' after -- Enum WebsocketConnectionType data WebsocketConnectionType = WebsocketConnectionTypeUnknown | WebsocketConnectionTypeClient | WebsocketConnectionTypeServer | AnotherWebsocketConnectionType Int deriving (Show, Eq) instance Enum WebsocketConnectionType where fromEnum WebsocketConnectionTypeUnknown = 0 fromEnum WebsocketConnectionTypeClient = 1 fromEnum WebsocketConnectionTypeServer = 2 fromEnum (AnotherWebsocketConnectionType k) = k toEnum 0 = WebsocketConnectionTypeUnknown toEnum 1 = WebsocketConnectionTypeClient toEnum 2 = WebsocketConnectionTypeServer toEnum k = AnotherWebsocketConnectionType k foreign import ccall "soup_websocket_connection_type_get_type" c_soup_websocket_connection_type_get_type :: IO GType instance BoxedEnum WebsocketConnectionType where boxedEnumType _ = c_soup_websocket_connection_type_get_type -- Enum WebsocketDataType data WebsocketDataType = WebsocketDataTypeText | WebsocketDataTypeBinary | AnotherWebsocketDataType Int deriving (Show, Eq) instance Enum WebsocketDataType where fromEnum WebsocketDataTypeText = 1 fromEnum WebsocketDataTypeBinary = 2 fromEnum (AnotherWebsocketDataType k) = k toEnum 1 = WebsocketDataTypeText toEnum 2 = WebsocketDataTypeBinary toEnum k = AnotherWebsocketDataType k foreign import ccall "soup_websocket_data_type_get_type" c_soup_websocket_data_type_get_type :: IO GType instance BoxedEnum WebsocketDataType where boxedEnumType _ = c_soup_websocket_data_type_get_type -- Enum WebsocketError data WebsocketError = WebsocketErrorFailed | WebsocketErrorNotWebsocket | WebsocketErrorBadHandshake | WebsocketErrorBadOrigin | AnotherWebsocketError Int deriving (Show, Eq) instance Enum WebsocketError where fromEnum WebsocketErrorFailed = 0 fromEnum WebsocketErrorNotWebsocket = 1 fromEnum WebsocketErrorBadHandshake = 2 fromEnum WebsocketErrorBadOrigin = 3 fromEnum (AnotherWebsocketError k) = k toEnum 0 = WebsocketErrorFailed toEnum 1 = WebsocketErrorNotWebsocket toEnum 2 = WebsocketErrorBadHandshake toEnum 3 = WebsocketErrorBadOrigin toEnum k = AnotherWebsocketError k foreign import ccall "soup_websocket_error_get_type" c_soup_websocket_error_get_type :: IO GType instance BoxedEnum WebsocketError where boxedEnumType _ = c_soup_websocket_error_get_type -- Enum WebsocketState data WebsocketState = WebsocketStateOpen | WebsocketStateClosing | WebsocketStateClosed | AnotherWebsocketState Int deriving (Show, Eq) instance Enum WebsocketState where fromEnum WebsocketStateOpen = 1 fromEnum WebsocketStateClosing = 2 fromEnum WebsocketStateClosed = 3 fromEnum (AnotherWebsocketState k) = k toEnum 1 = WebsocketStateOpen toEnum 2 = WebsocketStateClosing toEnum 3 = WebsocketStateClosed toEnum k = AnotherWebsocketState k foreign import ccall "soup_websocket_state_get_type" c_soup_websocket_state_get_type :: IO GType instance BoxedEnum WebsocketState where boxedEnumType _ = c_soup_websocket_state_get_type -- Enum XMLRPCError data XMLRPCError = XMLRPCErrorArguments | XMLRPCErrorRetval | AnotherXMLRPCError Int deriving (Show, Eq) instance Enum XMLRPCError where fromEnum XMLRPCErrorArguments = 0 fromEnum XMLRPCErrorRetval = 1 fromEnum (AnotherXMLRPCError k) = k toEnum 0 = XMLRPCErrorArguments toEnum 1 = XMLRPCErrorRetval toEnum k = AnotherXMLRPCError k instance GErrorClass XMLRPCError where gerrorClassDomain _ = "soup_xmlrpc_error_quark" catchXMLRPCError :: IO a -> (XMLRPCError -> GErrorMessage -> IO a) -> IO a catchXMLRPCError = catchGErrorJustDomain handleXMLRPCError :: (XMLRPCError -> GErrorMessage -> IO a) -> IO a -> IO a handleXMLRPCError = handleGErrorJustDomain foreign import ccall "soup_xmlrpc_error_get_type" c_soup_xmlrpc_error_get_type :: IO GType instance BoxedEnum XMLRPCError where boxedEnumType _ = c_soup_xmlrpc_error_get_type -- Enum XMLRPCFault data XMLRPCFault = XMLRPCFaultParseErrorNotWellFormed | XMLRPCFaultParseErrorUnsupportedEncoding | XMLRPCFaultParseErrorInvalidCharacterForEncoding | XMLRPCFaultServerErrorInvalidXmlRpc | XMLRPCFaultServerErrorRequestedMethodNotFound | XMLRPCFaultServerErrorInvalidMethodParameters | XMLRPCFaultServerErrorInternalXmlRpcError | XMLRPCFaultApplicationError | XMLRPCFaultSystemError | XMLRPCFaultTransportError | AnotherXMLRPCFault Int deriving (Show, Eq) instance Enum XMLRPCFault where fromEnum XMLRPCFaultParseErrorNotWellFormed = -32700 fromEnum XMLRPCFaultParseErrorUnsupportedEncoding = -32701 fromEnum XMLRPCFaultParseErrorInvalidCharacterForEncoding = -32702 fromEnum XMLRPCFaultServerErrorInvalidXmlRpc = -32600 fromEnum XMLRPCFaultServerErrorRequestedMethodNotFound = -32601 fromEnum XMLRPCFaultServerErrorInvalidMethodParameters = -32602 fromEnum XMLRPCFaultServerErrorInternalXmlRpcError = -32603 fromEnum XMLRPCFaultApplicationError = -32500 fromEnum XMLRPCFaultSystemError = -32400 fromEnum XMLRPCFaultTransportError = -32300 fromEnum (AnotherXMLRPCFault k) = k toEnum -32702 = XMLRPCFaultParseErrorInvalidCharacterForEncoding toEnum -32701 = XMLRPCFaultParseErrorUnsupportedEncoding toEnum -32700 = XMLRPCFaultParseErrorNotWellFormed toEnum -32603 = XMLRPCFaultServerErrorInternalXmlRpcError toEnum -32602 = XMLRPCFaultServerErrorInvalidMethodParameters toEnum -32601 = XMLRPCFaultServerErrorRequestedMethodNotFound toEnum -32600 = XMLRPCFaultServerErrorInvalidXmlRpc toEnum -32500 = XMLRPCFaultApplicationError toEnum -32400 = XMLRPCFaultSystemError toEnum -32300 = XMLRPCFaultTransportError toEnum k = AnotherXMLRPCFault k foreign import ccall "soup_xmlrpc_fault_get_type" c_soup_xmlrpc_fault_get_type :: IO GType instance BoxedEnum XMLRPCFault where boxedEnumType _ = c_soup_xmlrpc_fault_get_type -- constant _ADDRESS_ANY_PORT _ADDRESS_ANY_PORT :: Int32 _ADDRESS_ANY_PORT = 0 -- constant _ADDRESS_FAMILY _ADDRESS_FAMILY :: T.Text _ADDRESS_FAMILY = "family" -- constant _ADDRESS_NAME _ADDRESS_NAME :: T.Text _ADDRESS_NAME = "name" -- constant _ADDRESS_PHYSICAL _ADDRESS_PHYSICAL :: T.Text _ADDRESS_PHYSICAL = "physical" -- constant _ADDRESS_PORT _ADDRESS_PORT :: T.Text _ADDRESS_PORT = "port" -- constant _ADDRESS_PROTOCOL _ADDRESS_PROTOCOL :: T.Text _ADDRESS_PROTOCOL = "protocol" -- constant _ADDRESS_SOCKADDR _ADDRESS_SOCKADDR :: T.Text _ADDRESS_SOCKADDR = "sockaddr" -- constant _AUTH_DOMAIN_ADD_PATH _AUTH_DOMAIN_ADD_PATH :: T.Text _AUTH_DOMAIN_ADD_PATH = "add-path" -- constant _AUTH_DOMAIN_BASIC_AUTH_CALLBACK _AUTH_DOMAIN_BASIC_AUTH_CALLBACK :: T.Text _AUTH_DOMAIN_BASIC_AUTH_CALLBACK = "auth-callback" -- constant _AUTH_DOMAIN_BASIC_AUTH_DATA _AUTH_DOMAIN_BASIC_AUTH_DATA :: T.Text _AUTH_DOMAIN_BASIC_AUTH_DATA = "auth-data" -- constant _AUTH_DOMAIN_BASIC_H _AUTH_DOMAIN_BASIC_H :: Int32 _AUTH_DOMAIN_BASIC_H = 1 -- constant _AUTH_DOMAIN_DIGEST_AUTH_CALLBACK _AUTH_DOMAIN_DIGEST_AUTH_CALLBACK :: T.Text _AUTH_DOMAIN_DIGEST_AUTH_CALLBACK = "auth-callback" -- constant _AUTH_DOMAIN_DIGEST_AUTH_DATA _AUTH_DOMAIN_DIGEST_AUTH_DATA :: T.Text _AUTH_DOMAIN_DIGEST_AUTH_DATA = "auth-data" -- constant _AUTH_DOMAIN_DIGEST_H _AUTH_DOMAIN_DIGEST_H :: Int32 _AUTH_DOMAIN_DIGEST_H = 1 -- constant _AUTH_DOMAIN_FILTER _AUTH_DOMAIN_FILTER :: T.Text _AUTH_DOMAIN_FILTER = "filter" -- constant _AUTH_DOMAIN_FILTER_DATA _AUTH_DOMAIN_FILTER_DATA :: T.Text _AUTH_DOMAIN_FILTER_DATA = "filter-data" -- constant _AUTH_DOMAIN_GENERIC_AUTH_CALLBACK _AUTH_DOMAIN_GENERIC_AUTH_CALLBACK :: T.Text _AUTH_DOMAIN_GENERIC_AUTH_CALLBACK = "generic-auth-callback" -- constant _AUTH_DOMAIN_GENERIC_AUTH_DATA _AUTH_DOMAIN_GENERIC_AUTH_DATA :: T.Text _AUTH_DOMAIN_GENERIC_AUTH_DATA = "generic-auth-data" -- constant _AUTH_DOMAIN_H _AUTH_DOMAIN_H :: Int32 _AUTH_DOMAIN_H = 1 -- constant _AUTH_DOMAIN_PROXY _AUTH_DOMAIN_PROXY :: T.Text _AUTH_DOMAIN_PROXY = "proxy" -- constant _AUTH_DOMAIN_REALM _AUTH_DOMAIN_REALM :: T.Text _AUTH_DOMAIN_REALM = "realm" -- constant _AUTH_DOMAIN_REMOVE_PATH _AUTH_DOMAIN_REMOVE_PATH :: T.Text _AUTH_DOMAIN_REMOVE_PATH = "remove-path" -- constant _AUTH_H _AUTH_H :: Int32 _AUTH_H = 1 -- constant _AUTH_HOST _AUTH_HOST :: T.Text _AUTH_HOST = "host" -- constant _AUTH_IS_AUTHENTICATED _AUTH_IS_AUTHENTICATED :: T.Text _AUTH_IS_AUTHENTICATED = "is-authenticated" -- constant _AUTH_IS_FOR_PROXY _AUTH_IS_FOR_PROXY :: T.Text _AUTH_IS_FOR_PROXY = "is-for-proxy" -- constant _AUTH_MANAGER_H _AUTH_MANAGER_H :: Int32 _AUTH_MANAGER_H = 1 -- constant _AUTH_REALM _AUTH_REALM :: T.Text _AUTH_REALM = "realm" -- constant _AUTH_SCHEME_NAME _AUTH_SCHEME_NAME :: T.Text _AUTH_SCHEME_NAME = "scheme-name" -- constant _CACHE_H _CACHE_H :: Int32 _CACHE_H = 1 -- constant _CHAR_HTTP_CTL _CHAR_HTTP_CTL :: Int32 _CHAR_HTTP_CTL = 16 -- constant _CHAR_HTTP_SEPARATOR _CHAR_HTTP_SEPARATOR :: Int32 _CHAR_HTTP_SEPARATOR = 8 -- constant _CHAR_URI_GEN_DELIMS _CHAR_URI_GEN_DELIMS :: Int32 _CHAR_URI_GEN_DELIMS = 2 -- constant _CHAR_URI_PERCENT_ENCODED _CHAR_URI_PERCENT_ENCODED :: Int32 _CHAR_URI_PERCENT_ENCODED = 1 -- constant _CHAR_URI_SUB_DELIMS _CHAR_URI_SUB_DELIMS :: Int32 _CHAR_URI_SUB_DELIMS = 4 -- constant _CONTENT_DECODER_H _CONTENT_DECODER_H :: Int32 _CONTENT_DECODER_H = 1 -- constant _CONTENT_SNIFFER_H _CONTENT_SNIFFER_H :: Int32 _CONTENT_SNIFFER_H = 1 -- constant _COOKIE_H _COOKIE_H :: Int32 _COOKIE_H = 1 -- constant _COOKIE_JAR_ACCEPT_POLICY _COOKIE_JAR_ACCEPT_POLICY :: T.Text _COOKIE_JAR_ACCEPT_POLICY = "accept-policy" -- constant _COOKIE_JAR_DB_FILENAME _COOKIE_JAR_DB_FILENAME :: T.Text _COOKIE_JAR_DB_FILENAME = "filename" -- constant _COOKIE_JAR_DB_H _COOKIE_JAR_DB_H :: Int32 _COOKIE_JAR_DB_H = 1 -- constant _COOKIE_JAR_H _COOKIE_JAR_H :: Int32 _COOKIE_JAR_H = 1 -- constant _COOKIE_JAR_READ_ONLY _COOKIE_JAR_READ_ONLY :: T.Text _COOKIE_JAR_READ_ONLY = "read-only" -- constant _COOKIE_JAR_TEXT_FILENAME _COOKIE_JAR_TEXT_FILENAME :: T.Text _COOKIE_JAR_TEXT_FILENAME = "filename" -- constant _COOKIE_JAR_TEXT_H _COOKIE_JAR_TEXT_H :: Int32 _COOKIE_JAR_TEXT_H = 1 -- constant _COOKIE_MAX_AGE_ONE_DAY _COOKIE_MAX_AGE_ONE_DAY :: Int32 _COOKIE_MAX_AGE_ONE_DAY = 0 -- constant _COOKIE_MAX_AGE_ONE_HOUR _COOKIE_MAX_AGE_ONE_HOUR :: Int32 _COOKIE_MAX_AGE_ONE_HOUR = 3600 -- constant _COOKIE_MAX_AGE_ONE_WEEK _COOKIE_MAX_AGE_ONE_WEEK :: Int32 _COOKIE_MAX_AGE_ONE_WEEK = 0 -- constant _COOKIE_MAX_AGE_ONE_YEAR _COOKIE_MAX_AGE_ONE_YEAR :: Int32 _COOKIE_MAX_AGE_ONE_YEAR = 0 -- constant _DATE_H _DATE_H :: Int32 _DATE_H = 1 -- constant _FORM_H _FORM_H :: Int32 _FORM_H = 1 -- constant _FORM_MIME_TYPE_MULTIPART _FORM_MIME_TYPE_MULTIPART :: T.Text _FORM_MIME_TYPE_MULTIPART = "multipart/form-data" -- constant _FORM_MIME_TYPE_URLENCODED _FORM_MIME_TYPE_URLENCODED :: T.Text _FORM_MIME_TYPE_URLENCODED = "application/x-www-form-urlencoded" -- constant _HEADERS_H _HEADERS_H :: Int32 _HEADERS_H = 1 -- constant _LOGGER_H _LOGGER_H :: Int32 _LOGGER_H = 1 -- constant _MESSAGE_BODY_H _MESSAGE_BODY_H :: Int32 _MESSAGE_BODY_H = 1 -- constant _MESSAGE_FIRST_PARTY _MESSAGE_FIRST_PARTY :: T.Text _MESSAGE_FIRST_PARTY = "first-party" -- constant _MESSAGE_FLAGS _MESSAGE_FLAGS :: T.Text _MESSAGE_FLAGS = "flags" -- constant _MESSAGE_H _MESSAGE_H :: Int32 _MESSAGE_H = 1 -- constant _MESSAGE_HEADERS_H _MESSAGE_HEADERS_H :: Int32 _MESSAGE_HEADERS_H = 1 -- constant _MESSAGE_HTTP_VERSION _MESSAGE_HTTP_VERSION :: T.Text _MESSAGE_HTTP_VERSION = "http-version" -- constant _MESSAGE_METHOD _MESSAGE_METHOD :: T.Text _MESSAGE_METHOD = "method" -- constant _MESSAGE_PRIORITY _MESSAGE_PRIORITY :: T.Text _MESSAGE_PRIORITY = "priority" -- constant _MESSAGE_REASON_PHRASE _MESSAGE_REASON_PHRASE :: T.Text _MESSAGE_REASON_PHRASE = "reason-phrase" -- constant _MESSAGE_REQUEST_BODY _MESSAGE_REQUEST_BODY :: T.Text _MESSAGE_REQUEST_BODY = "request-body" -- constant _MESSAGE_REQUEST_BODY_DATA _MESSAGE_REQUEST_BODY_DATA :: T.Text _MESSAGE_REQUEST_BODY_DATA = "request-body-data" -- constant _MESSAGE_REQUEST_HEADERS _MESSAGE_REQUEST_HEADERS :: T.Text _MESSAGE_REQUEST_HEADERS = "request-headers" -- constant _MESSAGE_RESPONSE_BODY _MESSAGE_RESPONSE_BODY :: T.Text _MESSAGE_RESPONSE_BODY = "response-body" -- constant _MESSAGE_RESPONSE_BODY_DATA _MESSAGE_RESPONSE_BODY_DATA :: T.Text _MESSAGE_RESPONSE_BODY_DATA = "response-body-data" -- constant _MESSAGE_RESPONSE_HEADERS _MESSAGE_RESPONSE_HEADERS :: T.Text _MESSAGE_RESPONSE_HEADERS = "response-headers" -- constant _MESSAGE_SERVER_SIDE _MESSAGE_SERVER_SIDE :: T.Text _MESSAGE_SERVER_SIDE = "server-side" -- constant _MESSAGE_STATUS_CODE _MESSAGE_STATUS_CODE :: T.Text _MESSAGE_STATUS_CODE = "status-code" -- constant _MESSAGE_TLS_CERTIFICATE _MESSAGE_TLS_CERTIFICATE :: T.Text _MESSAGE_TLS_CERTIFICATE = "tls-certificate" -- constant _MESSAGE_TLS_ERRORS _MESSAGE_TLS_ERRORS :: T.Text _MESSAGE_TLS_ERRORS = "tls-errors" -- constant _MESSAGE_URI _MESSAGE_URI :: T.Text _MESSAGE_URI = "uri" -- constant _METHOD_H _METHOD_H :: Int32 _METHOD_H = 1 -- constant _MISC_H _MISC_H :: Int32 _MISC_H = 1 -- constant _MULTIPART_H _MULTIPART_H :: Int32 _MULTIPART_H = 1 -- constant _MULTIPART_INPUT_STREAM_H _MULTIPART_INPUT_STREAM_H :: Int32 _MULTIPART_INPUT_STREAM_H = 1 -- constant _PASSWORD_MANAGER_H _PASSWORD_MANAGER_H :: Int32 _PASSWORD_MANAGER_H = 1 -- constant _PROXY_RESOLVER_DEFAULT_H _PROXY_RESOLVER_DEFAULT_H :: Int32 _PROXY_RESOLVER_DEFAULT_H = 1 -- constant _PROXY_URI_RESOLVER_H _PROXY_URI_RESOLVER_H :: Int32 _PROXY_URI_RESOLVER_H = 1 -- constant _REQUESTER_H _REQUESTER_H :: Int32 _REQUESTER_H = 1 -- constant _REQUEST_DATA_H _REQUEST_DATA_H :: Int32 _REQUEST_DATA_H = 1 -- constant _REQUEST_FILE_H _REQUEST_FILE_H :: Int32 _REQUEST_FILE_H = 1 -- constant _REQUEST_H _REQUEST_H :: Int32 _REQUEST_H = 1 -- constant _REQUEST_HTTP_H _REQUEST_HTTP_H :: Int32 _REQUEST_HTTP_H = 1 -- constant _REQUEST_SESSION _REQUEST_SESSION :: T.Text _REQUEST_SESSION = "session" -- constant _REQUEST_URI _REQUEST_URI :: T.Text _REQUEST_URI = "uri" -- constant _SERVER_ASYNC_CONTEXT {-# DEPRECATED _SERVER_ASYNC_CONTEXT ["The new API uses the thread-default #GMainContext","rather than having an explicitly-specified one."]#-} _SERVER_ASYNC_CONTEXT :: T.Text _SERVER_ASYNC_CONTEXT = "async-context" -- constant _SERVER_H _SERVER_H :: Int32 _SERVER_H = 1 -- constant _SERVER_HTTPS_ALIASES _SERVER_HTTPS_ALIASES :: T.Text _SERVER_HTTPS_ALIASES = "https-aliases" -- constant _SERVER_HTTP_ALIASES _SERVER_HTTP_ALIASES :: T.Text _SERVER_HTTP_ALIASES = "http-aliases" -- constant _SERVER_INTERFACE {-# DEPRECATED _SERVER_INTERFACE ["#SoupServers can listen on multiple interfaces","at once now. Use soup_server_listen(), etc, to listen on an","interface, and soup_server_get_uris() to see what addresses","are being listened on."]#-} _SERVER_INTERFACE :: T.Text _SERVER_INTERFACE = "interface" -- constant _SERVER_PORT {-# DEPRECATED _SERVER_PORT ["#SoupServers can listen on multiple interfaces","at once now. Use soup_server_listen(), etc, to listen on a","port, and soup_server_get_uris() to see what ports are","being listened on."]#-} _SERVER_PORT :: T.Text _SERVER_PORT = "port" -- constant _SERVER_RAW_PATHS _SERVER_RAW_PATHS :: T.Text _SERVER_RAW_PATHS = "raw-paths" -- constant _SERVER_SERVER_HEADER _SERVER_SERVER_HEADER :: T.Text _SERVER_SERVER_HEADER = "server-header" -- constant _SERVER_SSL_CERT_FILE {-# DEPRECATED _SERVER_SSL_CERT_FILE ["use #SoupServer:tls-certificate or","soup_server_set_ssl_certificate()."]#-} _SERVER_SSL_CERT_FILE :: T.Text _SERVER_SSL_CERT_FILE = "ssl-cert-file" -- constant _SERVER_SSL_KEY_FILE {-# DEPRECATED _SERVER_SSL_KEY_FILE ["use #SoupServer:tls-certificate or","soup_server_set_ssl_certificate()."]#-} _SERVER_SSL_KEY_FILE :: T.Text _SERVER_SSL_KEY_FILE = "ssl-key-file" -- constant _SERVER_TLS_CERTIFICATE _SERVER_TLS_CERTIFICATE :: T.Text _SERVER_TLS_CERTIFICATE = "tls-certificate" -- constant _SESSION_ACCEPT_LANGUAGE _SESSION_ACCEPT_LANGUAGE :: T.Text _SESSION_ACCEPT_LANGUAGE = "accept-language" -- constant _SESSION_ACCEPT_LANGUAGE_AUTO _SESSION_ACCEPT_LANGUAGE_AUTO :: T.Text _SESSION_ACCEPT_LANGUAGE_AUTO = "accept-language-auto" -- constant _SESSION_ASYNC_CONTEXT _SESSION_ASYNC_CONTEXT :: T.Text _SESSION_ASYNC_CONTEXT = "async-context" -- constant _SESSION_ASYNC_H _SESSION_ASYNC_H :: Int32 _SESSION_ASYNC_H = 1 -- constant _SESSION_FEATURE_H _SESSION_FEATURE_H :: Int32 _SESSION_FEATURE_H = 1 -- constant _SESSION_H _SESSION_H :: Int32 _SESSION_H = 1 -- constant _SESSION_HTTPS_ALIASES _SESSION_HTTPS_ALIASES :: T.Text _SESSION_HTTPS_ALIASES = "https-aliases" -- constant _SESSION_HTTP_ALIASES _SESSION_HTTP_ALIASES :: T.Text _SESSION_HTTP_ALIASES = "http-aliases" -- constant _SESSION_IDLE_TIMEOUT _SESSION_IDLE_TIMEOUT :: T.Text _SESSION_IDLE_TIMEOUT = "idle-timeout" -- constant _SESSION_LOCAL_ADDRESS _SESSION_LOCAL_ADDRESS :: T.Text _SESSION_LOCAL_ADDRESS = "local-address" -- constant _SESSION_MAX_CONNS _SESSION_MAX_CONNS :: T.Text _SESSION_MAX_CONNS = "max-conns" -- constant _SESSION_MAX_CONNS_PER_HOST _SESSION_MAX_CONNS_PER_HOST :: T.Text _SESSION_MAX_CONNS_PER_HOST = "max-conns-per-host" -- constant _SESSION_PROXY_RESOLVER _SESSION_PROXY_RESOLVER :: T.Text _SESSION_PROXY_RESOLVER = "proxy-resolver" -- constant _SESSION_PROXY_URI _SESSION_PROXY_URI :: T.Text _SESSION_PROXY_URI = "proxy-uri" -- constant _SESSION_SSL_CA_FILE _SESSION_SSL_CA_FILE :: T.Text _SESSION_SSL_CA_FILE = "ssl-ca-file" -- constant _SESSION_SSL_STRICT _SESSION_SSL_STRICT :: T.Text _SESSION_SSL_STRICT = "ssl-strict" -- constant _SESSION_SSL_USE_SYSTEM_CA_FILE _SESSION_SSL_USE_SYSTEM_CA_FILE :: T.Text _SESSION_SSL_USE_SYSTEM_CA_FILE = "ssl-use-system-ca-file" -- constant _SESSION_SYNC_H _SESSION_SYNC_H :: Int32 _SESSION_SYNC_H = 1 -- constant _SESSION_TIMEOUT _SESSION_TIMEOUT :: T.Text _SESSION_TIMEOUT = "timeout" -- constant _SESSION_TLS_DATABASE _SESSION_TLS_DATABASE :: T.Text _SESSION_TLS_DATABASE = "tls-database" -- constant _SESSION_TLS_INTERACTION _SESSION_TLS_INTERACTION :: T.Text _SESSION_TLS_INTERACTION = "tls-interaction" -- constant _SESSION_USER_AGENT _SESSION_USER_AGENT :: T.Text _SESSION_USER_AGENT = "user-agent" -- constant _SESSION_USE_NTLM _SESSION_USE_NTLM :: T.Text _SESSION_USE_NTLM = "use-ntlm" -- constant _SESSION_USE_THREAD_CONTEXT _SESSION_USE_THREAD_CONTEXT :: T.Text _SESSION_USE_THREAD_CONTEXT = "use-thread-context" -- constant _SOCKET_ASYNC_CONTEXT _SOCKET_ASYNC_CONTEXT :: T.Text _SOCKET_ASYNC_CONTEXT = "async-context" -- constant _SOCKET_FLAG_NONBLOCKING _SOCKET_FLAG_NONBLOCKING :: T.Text _SOCKET_FLAG_NONBLOCKING = "non-blocking" -- constant _SOCKET_H _SOCKET_H :: Int32 _SOCKET_H = 1 -- constant _SOCKET_IS_SERVER _SOCKET_IS_SERVER :: T.Text _SOCKET_IS_SERVER = "is-server" -- constant _SOCKET_LOCAL_ADDRESS _SOCKET_LOCAL_ADDRESS :: T.Text _SOCKET_LOCAL_ADDRESS = "local-address" -- constant _SOCKET_REMOTE_ADDRESS _SOCKET_REMOTE_ADDRESS :: T.Text _SOCKET_REMOTE_ADDRESS = "remote-address" -- constant _SOCKET_SSL_CREDENTIALS _SOCKET_SSL_CREDENTIALS :: T.Text _SOCKET_SSL_CREDENTIALS = "ssl-creds" -- constant _SOCKET_SSL_FALLBACK _SOCKET_SSL_FALLBACK :: T.Text _SOCKET_SSL_FALLBACK = "ssl-fallback" -- constant _SOCKET_SSL_STRICT _SOCKET_SSL_STRICT :: T.Text _SOCKET_SSL_STRICT = "ssl-strict" -- constant _SOCKET_TIMEOUT _SOCKET_TIMEOUT :: T.Text _SOCKET_TIMEOUT = "timeout" -- constant _SOCKET_TLS_CERTIFICATE _SOCKET_TLS_CERTIFICATE :: T.Text _SOCKET_TLS_CERTIFICATE = "tls-certificate" -- constant _SOCKET_TLS_ERRORS _SOCKET_TLS_ERRORS :: T.Text _SOCKET_TLS_ERRORS = "tls-errors" -- constant _SOCKET_TRUSTED_CERTIFICATE _SOCKET_TRUSTED_CERTIFICATE :: T.Text _SOCKET_TRUSTED_CERTIFICATE = "trusted-certificate" -- constant _SOCKET_USE_THREAD_CONTEXT _SOCKET_USE_THREAD_CONTEXT :: T.Text _SOCKET_USE_THREAD_CONTEXT = "use-thread-context" -- constant _STATUS_H _STATUS_H :: Int32 _STATUS_H = 1 -- constant _TYPES_H _TYPES_H :: Int32 _TYPES_H = 1 -- constant _URI_H _URI_H :: Int32 _URI_H = 1 -- constant _VALUE_UTILS_H _VALUE_UTILS_H :: Int32 _VALUE_UTILS_H = 1 -- constant _XMLRPC_H _XMLRPC_H :: Int32 _XMLRPC_H = 1 -- function soup_cookie_parse -- Args : [Arg {argName = "header", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "origin", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "header", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "origin", argType = TInterface "Soup" "URI", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Cookie" -- throws : False -- Skip return : False foreign import ccall "soup_cookie_parse" soup_cookie_parse :: CString -> -- header : TBasicType TUTF8 Ptr URI -> -- origin : TInterface "Soup" "URI" IO (Ptr Cookie) cookieParse :: (MonadIO m) => T.Text -> -- header URI -> -- origin m Cookie cookieParse header origin = liftIO $ do header' <- textToCString header let origin' = unsafeManagedPtrGetPtr origin result <- soup_cookie_parse header' origin' checkUnexpectedReturnNULL "soup_cookie_parse" result result' <- (wrapBoxed Cookie) result touchManagedPtr origin freeMem header' return result' -- function soup_cookies_from_request -- Args : [Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TGSList (TInterface "Soup" "Cookie") -- throws : False -- Skip return : False foreign import ccall "soup_cookies_from_request" soup_cookies_from_request :: Ptr Message -> -- msg : TInterface "Soup" "Message" IO (Ptr (GSList (Ptr Cookie))) cookiesFromRequest :: (MonadIO m, MessageK a) => a -> -- msg m [Cookie] cookiesFromRequest msg = liftIO $ do let msg' = unsafeManagedPtrCastPtr msg result <- soup_cookies_from_request msg' checkUnexpectedReturnNULL "soup_cookies_from_request" result result' <- unpackGSList result result'' <- mapM (wrapBoxed Cookie) result' g_slist_free result touchManagedPtr msg return result'' -- function soup_cookies_from_response -- Args : [Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TGSList (TInterface "Soup" "Cookie") -- throws : False -- Skip return : False foreign import ccall "soup_cookies_from_response" soup_cookies_from_response :: Ptr Message -> -- msg : TInterface "Soup" "Message" IO (Ptr (GSList (Ptr Cookie))) cookiesFromResponse :: (MonadIO m, MessageK a) => a -> -- msg m [Cookie] cookiesFromResponse msg = liftIO $ do let msg' = unsafeManagedPtrCastPtr msg result <- soup_cookies_from_response msg' checkUnexpectedReturnNULL "soup_cookies_from_response" result result' <- unpackGSList result result'' <- mapM (wrapBoxed Cookie) result' g_slist_free result touchManagedPtr msg return result'' -- function soup_cookies_to_cookie_header -- Args : [Arg {argName = "cookies", argType = TGSList (TInterface "Soup" "Cookie"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "cookies", argType = TGSList (TInterface "Soup" "Cookie"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_cookies_to_cookie_header" soup_cookies_to_cookie_header :: Ptr (GSList (Ptr Cookie)) -> -- cookies : TGSList (TInterface "Soup" "Cookie") IO CString cookiesToCookieHeader :: (MonadIO m) => [Cookie] -> -- cookies m T.Text cookiesToCookieHeader cookies = liftIO $ do let cookies' = map unsafeManagedPtrGetPtr cookies cookies'' <- packGSList cookies' result <- soup_cookies_to_cookie_header cookies'' checkUnexpectedReturnNULL "soup_cookies_to_cookie_header" result result' <- cstringToText result freeMem result mapM_ touchManagedPtr cookies g_slist_free cookies'' return result' -- function soup_cookies_to_request -- Args : [Arg {argName = "cookies", argType = TGSList (TInterface "Soup" "Cookie"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "cookies", argType = TGSList (TInterface "Soup" "Cookie"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_cookies_to_request" soup_cookies_to_request :: Ptr (GSList (Ptr Cookie)) -> -- cookies : TGSList (TInterface "Soup" "Cookie") Ptr Message -> -- msg : TInterface "Soup" "Message" IO () cookiesToRequest :: (MonadIO m, MessageK a) => [Cookie] -> -- cookies a -> -- msg m () cookiesToRequest cookies msg = liftIO $ do let cookies' = map unsafeManagedPtrGetPtr cookies cookies'' <- packGSList cookies' let msg' = unsafeManagedPtrCastPtr msg soup_cookies_to_request cookies'' msg' mapM_ touchManagedPtr cookies touchManagedPtr msg g_slist_free cookies'' return () -- function soup_cookies_to_response -- Args : [Arg {argName = "cookies", argType = TGSList (TInterface "Soup" "Cookie"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "cookies", argType = TGSList (TInterface "Soup" "Cookie"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TVoid -- throws : False -- Skip return : False foreign import ccall "soup_cookies_to_response" soup_cookies_to_response :: Ptr (GSList (Ptr Cookie)) -> -- cookies : TGSList (TInterface "Soup" "Cookie") Ptr Message -> -- msg : TInterface "Soup" "Message" IO () cookiesToResponse :: (MonadIO m, MessageK a) => [Cookie] -> -- cookies a -> -- msg m () cookiesToResponse cookies msg = liftIO $ do let cookies' = map unsafeManagedPtrGetPtr cookies cookies'' <- packGSList cookies' let msg' = unsafeManagedPtrCastPtr msg soup_cookies_to_response cookies'' msg' mapM_ touchManagedPtr cookies touchManagedPtr msg g_slist_free cookies'' return () -- function soup_form_decode -- Args : [Arg {argName = "encoded_form", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "encoded_form", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TGHash (TBasicType TUTF8) (TBasicType TUTF8) -- throws : False -- Skip return : False foreign import ccall "soup_form_decode" soup_form_decode :: CString -> -- encoded_form : TBasicType TUTF8 IO (Ptr (GHashTable CString CString)) formDecode :: (MonadIO m) => T.Text -> -- encoded_form m (Map.Map T.Text T.Text) formDecode encoded_form = liftIO $ do encoded_form' <- textToCString encoded_form result <- soup_form_decode encoded_form' checkUnexpectedReturnNULL "soup_form_decode" result result' <- unpackGHashTable result let result'' = mapFirst cstringUnpackPtr result' result''' <- mapFirstA cstringToText result'' let result'''' = mapSecond cstringUnpackPtr result''' result''''' <- mapSecondA cstringToText result'''' let result'''''' = Map.fromList result''''' unrefGHashTable result freeMem encoded_form' return result'''''' -- function soup_form_decode_multipart -- Args : [Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file_control_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "content_type", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "file", argType = TInterface "Soup" "Buffer", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- Lengths : [] -- hInArgs : [Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file_control_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TGHash (TBasicType TUTF8) (TBasicType TUTF8) -- throws : False -- Skip return : False foreign import ccall "soup_form_decode_multipart" soup_form_decode_multipart :: Ptr Message -> -- msg : TInterface "Soup" "Message" CString -> -- file_control_name : TBasicType TUTF8 Ptr CString -> -- filename : TBasicType TUTF8 Ptr CString -> -- content_type : TBasicType TUTF8 Ptr Buffer -> -- file : TInterface "Soup" "Buffer" IO (Ptr (GHashTable CString CString)) formDecodeMultipart :: (MonadIO m, MessageK a) => a -> -- msg Maybe (T.Text) -> -- file_control_name m ((Map.Map T.Text T.Text),T.Text,T.Text,Buffer) formDecodeMultipart msg file_control_name = liftIO $ do let msg' = unsafeManagedPtrCastPtr msg maybeFile_control_name <- case file_control_name of Nothing -> return nullPtr Just jFile_control_name -> do jFile_control_name' <- textToCString jFile_control_name return jFile_control_name' filename <- allocMem :: IO (Ptr CString) content_type <- allocMem :: IO (Ptr CString) file <- callocBoxedBytes 16 :: IO (Ptr Buffer) result <- soup_form_decode_multipart msg' maybeFile_control_name filename content_type file checkUnexpectedReturnNULL "soup_form_decode_multipart" result result' <- unpackGHashTable result let result'' = mapFirst cstringUnpackPtr result' result''' <- mapFirstA cstringToText result'' let result'''' = mapSecond cstringUnpackPtr result''' result''''' <- mapSecondA cstringToText result'''' let result'''''' = Map.fromList result''''' unrefGHashTable result filename' <- peek filename filename'' <- cstringToText filename' freeMem filename' content_type' <- peek content_type content_type'' <- cstringToText content_type' freeMem content_type' file' <- (wrapBoxed Buffer) file touchManagedPtr msg freeMem maybeFile_control_name freeMem filename freeMem content_type return (result'''''', filename'', content_type'', file') -- function soup_form_encode_datalist -- Args : [Arg {argName = "form_data_set", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "form_data_set", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_form_encode_datalist" soup_form_encode_datalist :: Ptr GLib.Data -> -- form_data_set : TInterface "GLib" "Data" IO CString formEncodeDatalist :: (MonadIO m) => GLib.Data -> -- form_data_set m T.Text formEncodeDatalist form_data_set = liftIO $ do let form_data_set' = unsafeManagedPtrGetPtr form_data_set result <- soup_form_encode_datalist form_data_set' checkUnexpectedReturnNULL "soup_form_encode_datalist" result result' <- cstringToText result freeMem result touchManagedPtr form_data_set return result' -- function soup_form_encode_hash -- Args : [Arg {argName = "form_data_set", argType = TGHash (TBasicType TUTF8) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "form_data_set", argType = TGHash (TBasicType TUTF8) (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_form_encode_hash" soup_form_encode_hash :: Ptr (GHashTable CString CString) -> -- form_data_set : TGHash (TBasicType TUTF8) (TBasicType TUTF8) IO CString formEncodeHash :: (MonadIO m) => Map.Map T.Text T.Text -> -- form_data_set m T.Text formEncodeHash form_data_set = liftIO $ do let form_data_set' = Map.toList form_data_set form_data_set'' <- mapFirstA textToCString form_data_set' form_data_set''' <- mapSecondA textToCString form_data_set'' let form_data_set'''' = mapFirst cstringPackPtr form_data_set''' let form_data_set''''' = mapSecond cstringPackPtr form_data_set'''' form_data_set'''''' <- packGHashTable gStrHash gStrEqual (Just ptr_to_g_free) (Just ptr_to_g_free) form_data_set''''' result <- soup_form_encode_hash form_data_set'''''' checkUnexpectedReturnNULL "soup_form_encode_hash" result result' <- cstringToText result freeMem result unrefGHashTable form_data_set'''''' return result' -- function soup_form_request_new_from_datalist -- Args : [Arg {argName = "method", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "form_data_set", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "method", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "form_data_set", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Message" -- throws : False -- Skip return : False foreign import ccall "soup_form_request_new_from_datalist" soup_form_request_new_from_datalist :: CString -> -- method : TBasicType TUTF8 CString -> -- uri : TBasicType TUTF8 Ptr GLib.Data -> -- form_data_set : TInterface "GLib" "Data" IO (Ptr Message) formRequestNewFromDatalist :: (MonadIO m) => T.Text -> -- method T.Text -> -- uri GLib.Data -> -- form_data_set m Message formRequestNewFromDatalist method uri form_data_set = liftIO $ do method' <- textToCString method uri' <- textToCString uri let form_data_set' = unsafeManagedPtrGetPtr form_data_set result <- soup_form_request_new_from_datalist method' uri' form_data_set' checkUnexpectedReturnNULL "soup_form_request_new_from_datalist" result result' <- (wrapObject Message) result touchManagedPtr form_data_set freeMem method' freeMem uri' return result' -- function soup_form_request_new_from_hash -- Args : [Arg {argName = "method", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "form_data_set", argType = TGHash (TBasicType TUTF8) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "method", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "form_data_set", argType = TGHash (TBasicType TUTF8) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Message" -- throws : False -- Skip return : False foreign import ccall "soup_form_request_new_from_hash" soup_form_request_new_from_hash :: CString -> -- method : TBasicType TUTF8 CString -> -- uri : TBasicType TUTF8 Ptr (GHashTable CString CString) -> -- form_data_set : TGHash (TBasicType TUTF8) (TBasicType TUTF8) IO (Ptr Message) formRequestNewFromHash :: (MonadIO m) => T.Text -> -- method T.Text -> -- uri Map.Map T.Text T.Text -> -- form_data_set m Message formRequestNewFromHash method uri form_data_set = liftIO $ do method' <- textToCString method uri' <- textToCString uri let form_data_set' = Map.toList form_data_set form_data_set'' <- mapFirstA textToCString form_data_set' form_data_set''' <- mapSecondA textToCString form_data_set'' let form_data_set'''' = mapFirst cstringPackPtr form_data_set''' let form_data_set''''' = mapSecond cstringPackPtr form_data_set'''' form_data_set'''''' <- packGHashTable gStrHash gStrEqual (Just ptr_to_g_free) (Just ptr_to_g_free) form_data_set''''' result <- soup_form_request_new_from_hash method' uri' form_data_set'''''' checkUnexpectedReturnNULL "soup_form_request_new_from_hash" result result' <- (wrapObject Message) result freeMem method' freeMem uri' unrefGHashTable form_data_set'''''' return result' -- function soup_form_request_new_from_multipart -- Args : [Arg {argName = "uri", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "multipart", argType = TInterface "Soup" "Multipart", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "uri", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "multipart", argType = TInterface "Soup" "Multipart", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TInterface "Soup" "Message" -- throws : False -- Skip return : False foreign import ccall "soup_form_request_new_from_multipart" soup_form_request_new_from_multipart :: CString -> -- uri : TBasicType TUTF8 Ptr Multipart -> -- multipart : TInterface "Soup" "Multipart" IO (Ptr Message) formRequestNewFromMultipart :: (MonadIO m) => T.Text -> -- uri Multipart -> -- multipart m Message formRequestNewFromMultipart uri multipart = liftIO $ do uri' <- textToCString uri let multipart' = unsafeManagedPtrGetPtr multipart result <- soup_form_request_new_from_multipart uri' multipart' checkUnexpectedReturnNULL "soup_form_request_new_from_multipart" result result' <- (wrapObject Message) result touchManagedPtr multipart freeMem uri' return result' -- function soup_header_contains -- Args : [Arg {argName = "header", 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 = "header", 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_header_contains" soup_header_contains :: CString -> -- header : TBasicType TUTF8 CString -> -- token : TBasicType TUTF8 IO CInt headerContains :: (MonadIO m) => T.Text -> -- header T.Text -> -- token m Bool headerContains header token = liftIO $ do header' <- textToCString header token' <- textToCString token result <- soup_header_contains header' token' let result' = (/= 0) result freeMem header' freeMem token' return result' -- function soup_header_free_param_list -- Args : [Arg {argName = "param_list", argType = TGHash (TBasicType TUTF8) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "param_list", argType = TGHash (TBasicType TUTF8) (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_header_free_param_list" soup_header_free_param_list :: Ptr (GHashTable CString CString) -> -- param_list : TGHash (TBasicType TUTF8) (TBasicType TUTF8) IO () headerFreeParamList :: (MonadIO m) => Map.Map T.Text T.Text -> -- param_list m () headerFreeParamList param_list = liftIO $ do let param_list' = Map.toList param_list param_list'' <- mapFirstA textToCString param_list' param_list''' <- mapSecondA textToCString param_list'' let param_list'''' = mapFirst cstringPackPtr param_list''' let param_list''''' = mapSecond cstringPackPtr param_list'''' param_list'''''' <- packGHashTable gStrHash gStrEqual (Just ptr_to_g_free) (Just ptr_to_g_free) param_list''''' soup_header_free_param_list param_list'''''' unrefGHashTable param_list'''''' return () -- function soup_header_g_string_append_param -- Args : [Arg {argName = "string", argType = TInterface "GLib" "String", 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 = "string", argType = TInterface "GLib" "String", 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_header_g_string_append_param" soup_header_g_string_append_param :: Ptr GLib.String -> -- string : TInterface "GLib" "String" CString -> -- name : TBasicType TUTF8 CString -> -- value : TBasicType TUTF8 IO () headerGStringAppendParam :: (MonadIO m) => GLib.String -> -- string T.Text -> -- name T.Text -> -- value m () headerGStringAppendParam string name value = liftIO $ do let string' = unsafeManagedPtrGetPtr string name' <- textToCString name value' <- textToCString value soup_header_g_string_append_param string' name' value' touchManagedPtr string freeMem name' freeMem value' return () -- function soup_header_g_string_append_param_quoted -- Args : [Arg {argName = "string", argType = TInterface "GLib" "String", 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 = "string", argType = TInterface "GLib" "String", 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_header_g_string_append_param_quoted" soup_header_g_string_append_param_quoted :: Ptr GLib.String -> -- string : TInterface "GLib" "String" CString -> -- name : TBasicType TUTF8 CString -> -- value : TBasicType TUTF8 IO () headerGStringAppendParamQuoted :: (MonadIO m) => GLib.String -> -- string T.Text -> -- name T.Text -> -- value m () headerGStringAppendParamQuoted string name value = liftIO $ do let string' = unsafeManagedPtrGetPtr string name' <- textToCString name value' <- textToCString value soup_header_g_string_append_param_quoted string' name' value' touchManagedPtr string freeMem name' freeMem value' return () -- function soup_header_parse_list -- Args : [Arg {argName = "header", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "header", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TGSList (TBasicType TUTF8) -- throws : False -- Skip return : False foreign import ccall "soup_header_parse_list" soup_header_parse_list :: CString -> -- header : TBasicType TUTF8 IO (Ptr (GSList CString)) headerParseList :: (MonadIO m) => T.Text -> -- header m [T.Text] headerParseList header = liftIO $ do header' <- textToCString header result <- soup_header_parse_list header' checkUnexpectedReturnNULL "soup_header_parse_list" result result' <- unpackGSList result result'' <- mapM cstringToText result' mapGSList freeMem result g_slist_free result freeMem header' return result'' -- function soup_header_parse_param_list -- Args : [Arg {argName = "header", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "header", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TGHash (TBasicType TUTF8) (TBasicType TUTF8) -- throws : False -- Skip return : False foreign import ccall "soup_header_parse_param_list" soup_header_parse_param_list :: CString -> -- header : TBasicType TUTF8 IO (Ptr (GHashTable CString CString)) headerParseParamList :: (MonadIO m) => T.Text -> -- header m (Map.Map T.Text T.Text) headerParseParamList header = liftIO $ do header' <- textToCString header result <- soup_header_parse_param_list header' checkUnexpectedReturnNULL "soup_header_parse_param_list" result result' <- unpackGHashTable result let result'' = mapFirst cstringUnpackPtr result' result''' <- mapFirstA cstringToText result'' let result'''' = mapSecond cstringUnpackPtr result''' result''''' <- mapSecondA cstringToText result'''' let result'''''' = Map.fromList result''''' unrefGHashTable result freeMem header' return result'''''' -- function soup_header_parse_quality_list -- Args : [Arg {argName = "header", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "unacceptable", argType = TGSList (TBasicType TUTF8), direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- Lengths : [] -- hInArgs : [Arg {argName = "header", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TGSList (TBasicType TUTF8) -- throws : False -- Skip return : False foreign import ccall "soup_header_parse_quality_list" soup_header_parse_quality_list :: CString -> -- header : TBasicType TUTF8 Ptr (Ptr (GSList CString)) -> -- unacceptable : TGSList (TBasicType TUTF8) IO (Ptr (GSList CString)) headerParseQualityList :: (MonadIO m) => T.Text -> -- header m ([T.Text],[T.Text]) headerParseQualityList header = liftIO $ do header' <- textToCString header unacceptable <- allocMem :: IO (Ptr (Ptr (GSList CString))) result <- soup_header_parse_quality_list header' unacceptable checkUnexpectedReturnNULL "soup_header_parse_quality_list" result result' <- unpackGSList result result'' <- mapM cstringToText result' mapGSList freeMem result g_slist_free result unacceptable' <- peek unacceptable unacceptable'' <- unpackGSList unacceptable' unacceptable''' <- mapM cstringToText unacceptable'' mapGSList freeMem unacceptable' g_slist_free unacceptable' freeMem header' freeMem unacceptable return (result'', unacceptable''') -- function soup_header_parse_semi_param_list -- Args : [Arg {argName = "header", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "header", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TGHash (TBasicType TUTF8) (TBasicType TUTF8) -- throws : False -- Skip return : False foreign import ccall "soup_header_parse_semi_param_list" soup_header_parse_semi_param_list :: CString -> -- header : TBasicType TUTF8 IO (Ptr (GHashTable CString CString)) headerParseSemiParamList :: (MonadIO m) => T.Text -> -- header m (Map.Map T.Text T.Text) headerParseSemiParamList header = liftIO $ do header' <- textToCString header result <- soup_header_parse_semi_param_list header' checkUnexpectedReturnNULL "soup_header_parse_semi_param_list" result result' <- unpackGHashTable result let result'' = mapFirst cstringUnpackPtr result' result''' <- mapFirstA cstringToText result'' let result'''' = mapSecond cstringUnpackPtr result''' result''''' <- mapSecondA cstringToText result'''' let result'''''' = Map.fromList result''''' unrefGHashTable result freeMem header' return result'''''' -- function soup_headers_parse -- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dest", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dest", 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_headers_parse" soup_headers_parse :: CString -> -- str : TBasicType TUTF8 Int32 -> -- len : TBasicType TInt32 Ptr MessageHeaders -> -- dest : TInterface "Soup" "MessageHeaders" IO CInt headersParse :: (MonadIO m) => T.Text -> -- str Int32 -> -- len MessageHeaders -> -- dest m Bool headersParse str len dest = liftIO $ do str' <- textToCString str let dest' = unsafeManagedPtrGetPtr dest result <- soup_headers_parse str' len dest' let result' = (/= 0) result touchManagedPtr dest freeMem str' return result' -- function soup_headers_parse_request -- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "req_headers", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "req_method", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "req_path", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "ver", argType = TInterface "Soup" "HTTPVersion", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- Lengths : [] -- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "req_headers", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_headers_parse_request" soup_headers_parse_request :: CString -> -- str : TBasicType TUTF8 Int32 -> -- len : TBasicType TInt32 Ptr MessageHeaders -> -- req_headers : TInterface "Soup" "MessageHeaders" Ptr CString -> -- req_method : TBasicType TUTF8 Ptr CString -> -- req_path : TBasicType TUTF8 Ptr CUInt -> -- ver : TInterface "Soup" "HTTPVersion" IO Word32 headersParseRequest :: (MonadIO m) => T.Text -> -- str Int32 -> -- len MessageHeaders -> -- req_headers m (Word32,T.Text,T.Text,HTTPVersion) headersParseRequest str len req_headers = liftIO $ do str' <- textToCString str let req_headers' = unsafeManagedPtrGetPtr req_headers req_method <- allocMem :: IO (Ptr CString) req_path <- allocMem :: IO (Ptr CString) ver <- allocMem :: IO (Ptr CUInt) result <- soup_headers_parse_request str' len req_headers' req_method req_path ver req_method' <- peek req_method req_method'' <- cstringToText req_method' freeMem req_method' req_path' <- peek req_path req_path'' <- cstringToText req_path' freeMem req_path' ver' <- peek ver let ver'' = (toEnum . fromIntegral) ver' touchManagedPtr req_headers freeMem str' freeMem req_method freeMem req_path freeMem ver return (result, req_method'', req_path'', ver'') -- function soup_headers_parse_response -- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "headers", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ver", argType = TInterface "Soup" "HTTPVersion", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "status_code", argType = TBasicType TUInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "reason_phrase", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- Lengths : [] -- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "headers", 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_headers_parse_response" soup_headers_parse_response :: CString -> -- str : TBasicType TUTF8 Int32 -> -- len : TBasicType TInt32 Ptr MessageHeaders -> -- headers : TInterface "Soup" "MessageHeaders" Ptr CUInt -> -- ver : TInterface "Soup" "HTTPVersion" Ptr Word32 -> -- status_code : TBasicType TUInt32 Ptr CString -> -- reason_phrase : TBasicType TUTF8 IO CInt headersParseResponse :: (MonadIO m) => T.Text -> -- str Int32 -> -- len MessageHeaders -> -- headers m (Bool,HTTPVersion,Word32,T.Text) headersParseResponse str len headers = liftIO $ do str' <- textToCString str let headers' = unsafeManagedPtrGetPtr headers ver <- allocMem :: IO (Ptr CUInt) status_code <- allocMem :: IO (Ptr Word32) reason_phrase <- allocMem :: IO (Ptr CString) result <- soup_headers_parse_response str' len headers' ver status_code reason_phrase let result' = (/= 0) result ver' <- peek ver let ver'' = (toEnum . fromIntegral) ver' status_code' <- peek status_code reason_phrase' <- peek reason_phrase reason_phrase'' <- cstringToText reason_phrase' freeMem reason_phrase' touchManagedPtr headers freeMem str' freeMem ver freeMem status_code freeMem reason_phrase return (result', ver'', status_code', reason_phrase'') -- function soup_headers_parse_status_line -- Args : [Arg {argName = "status_line", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ver", argType = TInterface "Soup" "HTTPVersion", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "status_code", argType = TBasicType TUInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "reason_phrase", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- Lengths : [] -- hInArgs : [Arg {argName = "status_line", 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_headers_parse_status_line" soup_headers_parse_status_line :: CString -> -- status_line : TBasicType TUTF8 Ptr CUInt -> -- ver : TInterface "Soup" "HTTPVersion" Ptr Word32 -> -- status_code : TBasicType TUInt32 Ptr CString -> -- reason_phrase : TBasicType TUTF8 IO CInt headersParseStatusLine :: (MonadIO m) => T.Text -> -- status_line m (Bool,HTTPVersion,Word32,T.Text) headersParseStatusLine status_line = liftIO $ do status_line' <- textToCString status_line ver <- allocMem :: IO (Ptr CUInt) status_code <- allocMem :: IO (Ptr Word32) reason_phrase <- allocMem :: IO (Ptr CString) result <- soup_headers_parse_status_line status_line' ver status_code reason_phrase let result' = (/= 0) result ver' <- peek ver let ver'' = (toEnum . fromIntegral) ver' status_code' <- peek status_code reason_phrase' <- peek reason_phrase reason_phrase'' <- cstringToText reason_phrase' freeMem reason_phrase' freeMem status_line' freeMem ver freeMem status_code freeMem reason_phrase return (result', ver'', status_code', reason_phrase'') -- function soup_http_error_quark -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_http_error_quark" soup_http_error_quark :: IO Word32 httpErrorQuark :: (MonadIO m) => m Word32 httpErrorQuark = liftIO $ do result <- soup_http_error_quark return result -- function soup_message_headers_iter_init -- Args : [Arg {argName = "iter", argType = TInterface "Soup" "MessageHeadersIter", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hdrs", argType = TInterface "Soup" "MessageHeaders", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "hdrs", 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_iter_init" soup_message_headers_iter_init :: Ptr MessageHeadersIter -> -- iter : TInterface "Soup" "MessageHeadersIter" Ptr MessageHeaders -> -- hdrs : TInterface "Soup" "MessageHeaders" IO () messageHeadersIterInit :: (MonadIO m) => MessageHeaders -> -- hdrs m (MessageHeadersIter) messageHeadersIterInit hdrs = liftIO $ do iter <- callocBytes 24 :: IO (Ptr MessageHeadersIter) let hdrs' = unsafeManagedPtrGetPtr hdrs soup_message_headers_iter_init iter hdrs' iter' <- (wrapPtr MessageHeadersIter) iter touchManagedPtr hdrs return iter' -- function soup_request_error_quark -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_request_error_quark" soup_request_error_quark :: IO Word32 requestErrorQuark :: (MonadIO m) => m Word32 requestErrorQuark = liftIO $ do result <- soup_request_error_quark return result -- function soup_requester_error_quark -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_requester_error_quark" soup_requester_error_quark :: IO Word32 requesterErrorQuark :: (MonadIO m) => m Word32 requesterErrorQuark = liftIO $ do result <- soup_requester_error_quark return result -- function soup_status_get_phrase -- Args : [Arg {argName = "status_code", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "status_code", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_status_get_phrase" soup_status_get_phrase :: Word32 -> -- status_code : TBasicType TUInt32 IO CString statusGetPhrase :: (MonadIO m) => Word32 -> -- status_code m T.Text statusGetPhrase status_code = liftIO $ do result <- soup_status_get_phrase status_code checkUnexpectedReturnNULL "soup_status_get_phrase" result result' <- cstringToText result return result' -- function soup_status_proxify -- Args : [Arg {argName = "status_code", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "status_code", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_status_proxify" soup_status_proxify :: Word32 -> -- status_code : TBasicType TUInt32 IO Word32 statusProxify :: (MonadIO m) => Word32 -> -- status_code m Word32 statusProxify status_code = liftIO $ do result <- soup_status_proxify status_code return result -- function soup_str_case_equal -- Args : [Arg {argName = "v1", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "v2", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "v1", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "v2", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_str_case_equal" soup_str_case_equal :: Ptr () -> -- v1 : TBasicType TVoid Ptr () -> -- v2 : TBasicType TVoid IO CInt strCaseEqual :: (MonadIO m) => Ptr () -> -- v1 Ptr () -> -- v2 m Bool strCaseEqual v1 v2 = liftIO $ do result <- soup_str_case_equal v1 v2 let result' = (/= 0) result return result' -- function soup_str_case_hash -- Args : [Arg {argName = "key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_str_case_hash" soup_str_case_hash :: Ptr () -> -- key : TBasicType TVoid IO Word32 strCaseHash :: (MonadIO m) => Ptr () -> -- key m Word32 strCaseHash key = liftIO $ do result <- soup_str_case_hash key return result -- function soup_tld_domain_is_public_suffix -- Args : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "domain", 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_tld_domain_is_public_suffix" soup_tld_domain_is_public_suffix :: CString -> -- domain : TBasicType TUTF8 IO CInt tldDomainIsPublicSuffix :: (MonadIO m) => T.Text -> -- domain m Bool tldDomainIsPublicSuffix domain = liftIO $ do domain' <- textToCString domain result <- soup_tld_domain_is_public_suffix domain' let result' = (/= 0) result freeMem domain' return result' -- function soup_tld_error_quark -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_tld_error_quark" soup_tld_error_quark :: IO Word32 tldErrorQuark :: (MonadIO m) => m Word32 tldErrorQuark = liftIO $ do result <- soup_tld_error_quark return result -- function soup_tld_get_base_domain -- Args : [Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : True -- Skip return : False foreign import ccall "soup_tld_get_base_domain" soup_tld_get_base_domain :: CString -> -- hostname : TBasicType TUTF8 Ptr (Ptr GError) -> -- error IO CString tldGetBaseDomain :: (MonadIO m) => T.Text -> -- hostname m T.Text tldGetBaseDomain hostname = liftIO $ do hostname' <- textToCString hostname onException (do result <- propagateGError $ soup_tld_get_base_domain hostname' checkUnexpectedReturnNULL "soup_tld_get_base_domain" result result' <- cstringToText result freeMem hostname' return result' ) (do freeMem hostname' ) -- function soup_uri_decode -- Args : [Arg {argName = "part", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "part", 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_uri_decode" soup_uri_decode :: CString -> -- part : TBasicType TUTF8 IO CString uriDecode :: (MonadIO m) => T.Text -> -- part m T.Text uriDecode part = liftIO $ do part' <- textToCString part result <- soup_uri_decode part' checkUnexpectedReturnNULL "soup_uri_decode" result result' <- cstringToText result freeMem result freeMem part' return result' -- function soup_uri_encode -- Args : [Arg {argName = "part", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "escape_extra", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "part", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "escape_extra", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_uri_encode" soup_uri_encode :: CString -> -- part : TBasicType TUTF8 CString -> -- escape_extra : TBasicType TUTF8 IO CString uriEncode :: (MonadIO m) => T.Text -> -- part Maybe (T.Text) -> -- escape_extra m T.Text uriEncode part escape_extra = liftIO $ do part' <- textToCString part maybeEscape_extra <- case escape_extra of Nothing -> return nullPtr Just jEscape_extra -> do jEscape_extra' <- textToCString jEscape_extra return jEscape_extra' result <- soup_uri_encode part' maybeEscape_extra checkUnexpectedReturnNULL "soup_uri_encode" result result' <- cstringToText result freeMem result freeMem part' freeMem maybeEscape_extra return result' -- function soup_uri_normalize -- Args : [Arg {argName = "part", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "unescape_extra", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "part", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "unescape_extra", 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_uri_normalize" soup_uri_normalize :: CString -> -- part : TBasicType TUTF8 CString -> -- unescape_extra : TBasicType TUTF8 IO CString uriNormalize :: (MonadIO m) => T.Text -> -- part T.Text -> -- unescape_extra m T.Text uriNormalize part unescape_extra = liftIO $ do part' <- textToCString part unescape_extra' <- textToCString unescape_extra result <- soup_uri_normalize part' unescape_extra' checkUnexpectedReturnNULL "soup_uri_normalize" result result' <- cstringToText result freeMem result freeMem part' freeMem unescape_extra' return result' -- function soup_value_array_new -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TInterface "GObject" "ValueArray" -- throws : False -- Skip return : False foreign import ccall "soup_value_array_new" soup_value_array_new :: IO (Ptr GObject.ValueArray) valueArrayNew :: (MonadIO m) => m GObject.ValueArray valueArrayNew = liftIO $ do result <- soup_value_array_new checkUnexpectedReturnNULL "soup_value_array_new" result result' <- (wrapBoxed GObject.ValueArray) result return result' -- function soup_value_hash_insert_value -- XXX Could not generate function soup_value_hash_insert_value -- Error was : Not implemented: "GHashTable element of type TInterface \"GObject\" \"Value\" unsupported." -- function soup_value_hash_new -- XXX Could not generate function soup_value_hash_new -- Error was : Not implemented: "GHashTable element of type TInterface \"GObject\" \"Value\" unsupported." -- function soup_websocket_client_prepare_handshake -- Args : [Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "origin", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "protocols", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "origin", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "protocols", argType = TCArray True (-1) (-1) (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_websocket_client_prepare_handshake" soup_websocket_client_prepare_handshake :: Ptr Message -> -- msg : TInterface "Soup" "Message" CString -> -- origin : TBasicType TUTF8 Ptr CString -> -- protocols : TCArray True (-1) (-1) (TBasicType TUTF8) IO () websocketClientPrepareHandshake :: (MonadIO m, MessageK a) => a -> -- msg Maybe (T.Text) -> -- origin Maybe ([T.Text]) -> -- protocols m () websocketClientPrepareHandshake msg origin protocols = liftIO $ do let msg' = unsafeManagedPtrCastPtr msg maybeOrigin <- case origin of Nothing -> return nullPtr Just jOrigin -> do jOrigin' <- textToCString jOrigin return jOrigin' maybeProtocols <- case protocols of Nothing -> return nullPtr Just jProtocols -> do jProtocols' <- packZeroTerminatedUTF8CArray jProtocols return jProtocols' soup_websocket_client_prepare_handshake msg' maybeOrigin maybeProtocols touchManagedPtr msg freeMem maybeOrigin mapZeroTerminatedCArray freeMem maybeProtocols freeMem maybeProtocols return () -- function soup_websocket_client_verify_handshake -- Args : [Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : True -- Skip return : False foreign import ccall "soup_websocket_client_verify_handshake" soup_websocket_client_verify_handshake :: Ptr Message -> -- msg : TInterface "Soup" "Message" Ptr (Ptr GError) -> -- error IO CInt websocketClientVerifyHandshake :: (MonadIO m, MessageK a) => a -> -- msg m () websocketClientVerifyHandshake msg = liftIO $ do let msg' = unsafeManagedPtrCastPtr msg onException (do _ <- propagateGError $ soup_websocket_client_verify_handshake msg' touchManagedPtr msg return () ) (do return () ) -- function soup_websocket_error_get_quark -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_websocket_error_get_quark" soup_websocket_error_get_quark :: IO Word32 websocketErrorGetQuark :: (MonadIO m) => m Word32 websocketErrorGetQuark = liftIO $ do result <- soup_websocket_error_get_quark return result -- function soup_websocket_server_check_handshake -- Args : [Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "origin", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "protocols", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "origin", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "protocols", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : True -- Skip return : False foreign import ccall "soup_websocket_server_check_handshake" soup_websocket_server_check_handshake :: Ptr Message -> -- msg : TInterface "Soup" "Message" CString -> -- origin : TBasicType TUTF8 Ptr CString -> -- protocols : TCArray True (-1) (-1) (TBasicType TUTF8) Ptr (Ptr GError) -> -- error IO CInt websocketServerCheckHandshake :: (MonadIO m, MessageK a) => a -> -- msg Maybe (T.Text) -> -- origin Maybe ([T.Text]) -> -- protocols m () websocketServerCheckHandshake msg origin protocols = liftIO $ do let msg' = unsafeManagedPtrCastPtr msg maybeOrigin <- case origin of Nothing -> return nullPtr Just jOrigin -> do jOrigin' <- textToCString jOrigin return jOrigin' maybeProtocols <- case protocols of Nothing -> return nullPtr Just jProtocols -> do jProtocols' <- packZeroTerminatedUTF8CArray jProtocols return jProtocols' onException (do _ <- propagateGError $ soup_websocket_server_check_handshake msg' maybeOrigin maybeProtocols touchManagedPtr msg freeMem maybeOrigin mapZeroTerminatedCArray freeMem maybeProtocols freeMem maybeProtocols return () ) (do freeMem maybeOrigin mapZeroTerminatedCArray freeMem maybeProtocols freeMem maybeProtocols ) -- function soup_websocket_server_process_handshake -- Args : [Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "origin", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "protocols", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "msg", argType = TInterface "Soup" "Message", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "origin", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "protocols", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_websocket_server_process_handshake" soup_websocket_server_process_handshake :: Ptr Message -> -- msg : TInterface "Soup" "Message" CString -> -- origin : TBasicType TUTF8 Ptr CString -> -- protocols : TCArray True (-1) (-1) (TBasicType TUTF8) IO CInt websocketServerProcessHandshake :: (MonadIO m, MessageK a) => a -> -- msg Maybe (T.Text) -> -- origin Maybe ([T.Text]) -> -- protocols m Bool websocketServerProcessHandshake msg origin protocols = liftIO $ do let msg' = unsafeManagedPtrCastPtr msg maybeOrigin <- case origin of Nothing -> return nullPtr Just jOrigin -> do jOrigin' <- textToCString jOrigin return jOrigin' maybeProtocols <- case protocols of Nothing -> return nullPtr Just jProtocols -> do jProtocols' <- packZeroTerminatedUTF8CArray jProtocols return jProtocols' result <- soup_websocket_server_process_handshake msg' maybeOrigin maybeProtocols let result' = (/= 0) result touchManagedPtr msg freeMem maybeOrigin mapZeroTerminatedCArray freeMem maybeProtocols freeMem maybeProtocols return result' -- function soup_xmlrpc_build_method_call -- Args : [Arg {argName = "method_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "params", argType = TCArray False (-1) 2 (TInterface "GObject" "Value"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n_params", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [Arg {argName = "n_params", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- hInArgs : [Arg {argName = "method_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "params", argType = TCArray False (-1) 2 (TInterface "GObject" "Value"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_xmlrpc_build_method_call" soup_xmlrpc_build_method_call :: CString -> -- method_name : TBasicType TUTF8 Ptr GValue -> -- params : TCArray False (-1) 2 (TInterface "GObject" "Value") Int32 -> -- n_params : TBasicType TInt32 IO CString xmlrpcBuildMethodCall :: (MonadIO m) => T.Text -> -- method_name [GValue] -> -- params m T.Text xmlrpcBuildMethodCall method_name params = liftIO $ do let n_params = fromIntegral $ length params method_name' <- textToCString method_name let params' = map unsafeManagedPtrGetPtr params params'' <- packBlockArray 24 params' result <- soup_xmlrpc_build_method_call method_name' params'' n_params checkUnexpectedReturnNULL "soup_xmlrpc_build_method_call" result result' <- cstringToText result freeMem result mapM_ touchManagedPtr params freeMem method_name' freeMem params'' return result' -- function soup_xmlrpc_build_method_response -- Args : [Arg {argName = "value", argType = TInterface "GObject" "Value", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "value", argType = TInterface "GObject" "Value", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- returnType : TBasicType TUTF8 -- throws : False -- Skip return : False foreign import ccall "soup_xmlrpc_build_method_response" soup_xmlrpc_build_method_response :: Ptr GValue -> -- value : TInterface "GObject" "Value" IO CString xmlrpcBuildMethodResponse :: (MonadIO m) => GValue -> -- value m T.Text xmlrpcBuildMethodResponse value = liftIO $ do let value' = unsafeManagedPtrGetPtr value result <- soup_xmlrpc_build_method_response value' checkUnexpectedReturnNULL "soup_xmlrpc_build_method_response" result result' <- cstringToText result freeMem result touchManagedPtr value return result' -- function soup_xmlrpc_error_quark -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_xmlrpc_error_quark" soup_xmlrpc_error_quark :: IO Word32 xmlrpcErrorQuark :: (MonadIO m) => m Word32 xmlrpcErrorQuark = liftIO $ do result <- soup_xmlrpc_error_quark return result -- function soup_xmlrpc_fault_quark -- Args : [] -- Lengths : [] -- hInArgs : [] -- returnType : TBasicType TUInt32 -- throws : False -- Skip return : False foreign import ccall "soup_xmlrpc_fault_quark" soup_xmlrpc_fault_quark :: IO Word32 xmlrpcFaultQuark :: (MonadIO m) => m Word32 xmlrpcFaultQuark = liftIO $ do result <- soup_xmlrpc_fault_quark return result -- function soup_xmlrpc_parse_method_call -- Args : [Arg {argName = "method_call", argType = TBasicType TUTF8, 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},Arg {argName = "method_name", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "params", argType = TInterface "GObject" "ValueArray", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}] -- Lengths : [] -- hInArgs : [Arg {argName = "method_call", argType = TBasicType TUTF8, 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 TBoolean -- throws : False -- Skip return : False foreign import ccall "soup_xmlrpc_parse_method_call" soup_xmlrpc_parse_method_call :: CString -> -- method_call : TBasicType TUTF8 Int32 -> -- length : TBasicType TInt32 Ptr CString -> -- method_name : TBasicType TUTF8 Ptr GObject.ValueArray -> -- params : TInterface "GObject" "ValueArray" IO CInt xmlrpcParseMethodCall :: (MonadIO m) => T.Text -> -- method_call Int32 -> -- length m (Bool,T.Text,GObject.ValueArray) xmlrpcParseMethodCall method_call length_ = liftIO $ do method_call' <- textToCString method_call method_name <- allocMem :: IO (Ptr CString) params <- callocBoxedBytes 24 :: IO (Ptr GObject.ValueArray) result <- soup_xmlrpc_parse_method_call method_call' length_ method_name params let result' = (/= 0) result method_name' <- peek method_name method_name'' <- cstringToText method_name' freeMem method_name' params' <- (wrapBoxed GObject.ValueArray) params freeMem method_call' freeMem method_name return (result', method_name'', params') -- function soup_xmlrpc_parse_method_response -- Args : [Arg {argName = "method_response", argType = TBasicType TUTF8, 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},Arg {argName = "value", argType = TInterface "GObject" "Value", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}] -- Lengths : [] -- hInArgs : [Arg {argName = "method_response", argType = TBasicType TUTF8, 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 TBoolean -- throws : True -- Skip return : False foreign import ccall "soup_xmlrpc_parse_method_response" soup_xmlrpc_parse_method_response :: CString -> -- method_response : TBasicType TUTF8 Int32 -> -- length : TBasicType TInt32 Ptr GValue -> -- value : TInterface "GObject" "Value" Ptr (Ptr GError) -> -- error IO CInt xmlrpcParseMethodResponse :: (MonadIO m) => T.Text -> -- method_response Int32 -> -- length m (GValue) xmlrpcParseMethodResponse method_response length_ = liftIO $ do method_response' <- textToCString method_response value <- callocBoxedBytes 24 :: IO (Ptr GValue) onException (do _ <- propagateGError $ soup_xmlrpc_parse_method_response method_response' length_ value value' <- (wrapBoxed GValue) value freeMem method_response' return value' ) (do freeMem method_response' freeMem value )