{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Soup.Objects.Server
(
Server(..) ,
IsServer ,
toServer ,
#if defined(ENABLE_OVERLOADING)
ResolveServerMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ServerAcceptIostreamMethodInfo ,
#endif
serverAcceptIostream ,
#if defined(ENABLE_OVERLOADING)
ServerAddAuthDomainMethodInfo ,
#endif
serverAddAuthDomain ,
#if defined(ENABLE_OVERLOADING)
ServerAddEarlyHandlerMethodInfo ,
#endif
serverAddEarlyHandler ,
#if defined(ENABLE_OVERLOADING)
ServerAddHandlerMethodInfo ,
#endif
serverAddHandler ,
#if defined(ENABLE_OVERLOADING)
ServerAddWebsocketExtensionMethodInfo ,
#endif
serverAddWebsocketExtension ,
#if defined(ENABLE_OVERLOADING)
ServerAddWebsocketHandlerMethodInfo ,
#endif
serverAddWebsocketHandler ,
#if defined(ENABLE_OVERLOADING)
ServerDisconnectMethodInfo ,
#endif
serverDisconnect ,
#if defined(ENABLE_OVERLOADING)
ServerGetAsyncContextMethodInfo ,
#endif
serverGetAsyncContext ,
#if defined(ENABLE_OVERLOADING)
ServerGetListenerMethodInfo ,
#endif
serverGetListener ,
#if defined(ENABLE_OVERLOADING)
ServerGetListenersMethodInfo ,
#endif
serverGetListeners ,
#if defined(ENABLE_OVERLOADING)
ServerGetPortMethodInfo ,
#endif
serverGetPort ,
#if defined(ENABLE_OVERLOADING)
ServerGetUrisMethodInfo ,
#endif
serverGetUris ,
#if defined(ENABLE_OVERLOADING)
ServerIsHttpsMethodInfo ,
#endif
serverIsHttps ,
#if defined(ENABLE_OVERLOADING)
ServerListenMethodInfo ,
#endif
serverListen ,
#if defined(ENABLE_OVERLOADING)
ServerListenAllMethodInfo ,
#endif
serverListenAll ,
#if defined(ENABLE_OVERLOADING)
ServerListenFdMethodInfo ,
#endif
serverListenFd ,
#if defined(ENABLE_OVERLOADING)
ServerListenLocalMethodInfo ,
#endif
serverListenLocal ,
#if defined(ENABLE_OVERLOADING)
ServerListenSocketMethodInfo ,
#endif
serverListenSocket ,
#if defined(ENABLE_OVERLOADING)
ServerPauseMessageMethodInfo ,
#endif
serverPauseMessage ,
#if defined(ENABLE_OVERLOADING)
ServerQuitMethodInfo ,
#endif
serverQuit ,
#if defined(ENABLE_OVERLOADING)
ServerRemoveAuthDomainMethodInfo ,
#endif
serverRemoveAuthDomain ,
#if defined(ENABLE_OVERLOADING)
ServerRemoveHandlerMethodInfo ,
#endif
serverRemoveHandler ,
#if defined(ENABLE_OVERLOADING)
ServerRemoveWebsocketExtensionMethodInfo,
#endif
serverRemoveWebsocketExtension ,
#if defined(ENABLE_OVERLOADING)
ServerRunMethodInfo ,
#endif
serverRun ,
#if defined(ENABLE_OVERLOADING)
ServerRunAsyncMethodInfo ,
#endif
serverRunAsync ,
#if defined(ENABLE_OVERLOADING)
ServerSetSslCertFileMethodInfo ,
#endif
serverSetSslCertFile ,
#if defined(ENABLE_OVERLOADING)
ServerUnpauseMessageMethodInfo ,
#endif
serverUnpauseMessage ,
#if defined(ENABLE_OVERLOADING)
ServerAsyncContextPropertyInfo ,
#endif
constructServerAsyncContext ,
getServerAsyncContext ,
#if defined(ENABLE_OVERLOADING)
serverAsyncContext ,
#endif
#if defined(ENABLE_OVERLOADING)
ServerHttpAliasesPropertyInfo ,
#endif
clearServerHttpAliases ,
constructServerHttpAliases ,
getServerHttpAliases ,
#if defined(ENABLE_OVERLOADING)
serverHttpAliases ,
#endif
setServerHttpAliases ,
#if defined(ENABLE_OVERLOADING)
ServerHttpsAliasesPropertyInfo ,
#endif
clearServerHttpsAliases ,
constructServerHttpsAliases ,
getServerHttpsAliases ,
#if defined(ENABLE_OVERLOADING)
serverHttpsAliases ,
#endif
setServerHttpsAliases ,
#if defined(ENABLE_OVERLOADING)
ServerInterfacePropertyInfo ,
#endif
constructServerInterface ,
getServerInterface ,
#if defined(ENABLE_OVERLOADING)
serverInterface ,
#endif
#if defined(ENABLE_OVERLOADING)
ServerPortPropertyInfo ,
#endif
constructServerPort ,
getServerPort ,
#if defined(ENABLE_OVERLOADING)
serverPort ,
#endif
#if defined(ENABLE_OVERLOADING)
ServerRawPathsPropertyInfo ,
#endif
constructServerRawPaths ,
getServerRawPaths ,
#if defined(ENABLE_OVERLOADING)
serverRawPaths ,
#endif
#if defined(ENABLE_OVERLOADING)
ServerServerHeaderPropertyInfo ,
#endif
clearServerServerHeader ,
constructServerServerHeader ,
getServerServerHeader ,
#if defined(ENABLE_OVERLOADING)
serverServerHeader ,
#endif
setServerServerHeader ,
#if defined(ENABLE_OVERLOADING)
ServerSslCertFilePropertyInfo ,
#endif
constructServerSslCertFile ,
getServerSslCertFile ,
#if defined(ENABLE_OVERLOADING)
serverSslCertFile ,
#endif
#if defined(ENABLE_OVERLOADING)
ServerSslKeyFilePropertyInfo ,
#endif
constructServerSslKeyFile ,
getServerSslKeyFile ,
#if defined(ENABLE_OVERLOADING)
serverSslKeyFile ,
#endif
#if defined(ENABLE_OVERLOADING)
ServerTlsCertificatePropertyInfo ,
#endif
constructServerTlsCertificate ,
getServerTlsCertificate ,
#if defined(ENABLE_OVERLOADING)
serverTlsCertificate ,
#endif
C_ServerRequestAbortedCallback ,
ServerRequestAbortedCallback ,
#if defined(ENABLE_OVERLOADING)
ServerRequestAbortedSignalInfo ,
#endif
afterServerRequestAborted ,
genClosure_ServerRequestAborted ,
mk_ServerRequestAbortedCallback ,
noServerRequestAbortedCallback ,
onServerRequestAborted ,
wrap_ServerRequestAbortedCallback ,
C_ServerRequestFinishedCallback ,
ServerRequestFinishedCallback ,
#if defined(ENABLE_OVERLOADING)
ServerRequestFinishedSignalInfo ,
#endif
afterServerRequestFinished ,
genClosure_ServerRequestFinished ,
mk_ServerRequestFinishedCallback ,
noServerRequestFinishedCallback ,
onServerRequestFinished ,
wrap_ServerRequestFinishedCallback ,
C_ServerRequestReadCallback ,
ServerRequestReadCallback ,
#if defined(ENABLE_OVERLOADING)
ServerRequestReadSignalInfo ,
#endif
afterServerRequestRead ,
genClosure_ServerRequestRead ,
mk_ServerRequestReadCallback ,
noServerRequestReadCallback ,
onServerRequestRead ,
wrap_ServerRequestReadCallback ,
C_ServerRequestStartedCallback ,
ServerRequestStartedCallback ,
#if defined(ENABLE_OVERLOADING)
ServerRequestStartedSignalInfo ,
#endif
afterServerRequestStarted ,
genClosure_ServerRequestStarted ,
mk_ServerRequestStartedCallback ,
noServerRequestStartedCallback ,
onServerRequestStarted ,
wrap_ServerRequestStartedCallback ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.MainContext as GLib.MainContext
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Objects.IOStream as Gio.IOStream
import qualified GI.Gio.Objects.Socket as Gio.Socket
import qualified GI.Gio.Objects.SocketAddress as Gio.SocketAddress
import qualified GI.Gio.Objects.TlsCertificate as Gio.TlsCertificate
import qualified GI.Soup.Callbacks as Soup.Callbacks
import {-# SOURCE #-} qualified GI.Soup.Flags as Soup.Flags
import {-# SOURCE #-} qualified GI.Soup.Objects.Address as Soup.Address
import {-# SOURCE #-} qualified GI.Soup.Objects.AuthDomain as Soup.AuthDomain
import {-# SOURCE #-} qualified GI.Soup.Objects.Message as Soup.Message
import {-# SOURCE #-} qualified GI.Soup.Objects.Socket as Soup.Socket
import {-# SOURCE #-} qualified GI.Soup.Structs.ClientContext as Soup.ClientContext
import {-# SOURCE #-} qualified GI.Soup.Structs.URI as Soup.URI
newtype Server = Server (SP.ManagedPtr Server)
deriving (Server -> Server -> Bool
(Server -> Server -> Bool)
-> (Server -> Server -> Bool) -> Eq Server
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Server -> Server -> Bool
$c/= :: Server -> Server -> Bool
== :: Server -> Server -> Bool
$c== :: Server -> Server -> Bool
Eq)
instance SP.ManagedPtrNewtype Server where
toManagedPtr :: Server -> ManagedPtr Server
toManagedPtr (Server ManagedPtr Server
p) = ManagedPtr Server
p
foreign import ccall "soup_server_get_type"
c_soup_server_get_type :: IO B.Types.GType
instance B.Types.TypedObject Server where
glibType :: IO GType
glibType = IO GType
c_soup_server_get_type
instance B.Types.GObject Server
instance B.GValue.IsGValue Server where
toGValue :: Server -> IO GValue
toGValue Server
o = do
GType
gtype <- IO GType
c_soup_server_get_type
Server -> (Ptr Server -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Server
o (GType -> (GValue -> Ptr Server -> IO ()) -> Ptr Server -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Server -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO Server
fromGValue GValue
gv = do
Ptr Server
ptr <- GValue -> IO (Ptr Server)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Server)
(ManagedPtr Server -> Server) -> Ptr Server -> IO Server
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Server -> Server
Server Ptr Server
ptr
class (SP.GObject o, O.IsDescendantOf Server o) => IsServer o
instance (SP.GObject o, O.IsDescendantOf Server o) => IsServer o
instance O.HasParentTypes Server
type instance O.ParentTypes Server = '[GObject.Object.Object]
toServer :: (MonadIO m, IsServer o) => o -> m Server
toServer :: o -> m Server
toServer = IO Server -> m Server
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Server -> m Server) -> (o -> IO Server) -> o -> m Server
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Server -> Server) -> o -> IO Server
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Server -> Server
Server
#if defined(ENABLE_OVERLOADING)
type family ResolveServerMethod (t :: Symbol) (o :: *) :: * where
ResolveServerMethod "acceptIostream" o = ServerAcceptIostreamMethodInfo
ResolveServerMethod "addAuthDomain" o = ServerAddAuthDomainMethodInfo
ResolveServerMethod "addEarlyHandler" o = ServerAddEarlyHandlerMethodInfo
ResolveServerMethod "addHandler" o = ServerAddHandlerMethodInfo
ResolveServerMethod "addWebsocketExtension" o = ServerAddWebsocketExtensionMethodInfo
ResolveServerMethod "addWebsocketHandler" o = ServerAddWebsocketHandlerMethodInfo
ResolveServerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveServerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveServerMethod "disconnect" o = ServerDisconnectMethodInfo
ResolveServerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveServerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveServerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveServerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveServerMethod "isHttps" o = ServerIsHttpsMethodInfo
ResolveServerMethod "listen" o = ServerListenMethodInfo
ResolveServerMethod "listenAll" o = ServerListenAllMethodInfo
ResolveServerMethod "listenFd" o = ServerListenFdMethodInfo
ResolveServerMethod "listenLocal" o = ServerListenLocalMethodInfo
ResolveServerMethod "listenSocket" o = ServerListenSocketMethodInfo
ResolveServerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveServerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveServerMethod "pauseMessage" o = ServerPauseMessageMethodInfo
ResolveServerMethod "quit" o = ServerQuitMethodInfo
ResolveServerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveServerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveServerMethod "removeAuthDomain" o = ServerRemoveAuthDomainMethodInfo
ResolveServerMethod "removeHandler" o = ServerRemoveHandlerMethodInfo
ResolveServerMethod "removeWebsocketExtension" o = ServerRemoveWebsocketExtensionMethodInfo
ResolveServerMethod "run" o = ServerRunMethodInfo
ResolveServerMethod "runAsync" o = ServerRunAsyncMethodInfo
ResolveServerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveServerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveServerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveServerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveServerMethod "unpauseMessage" o = ServerUnpauseMessageMethodInfo
ResolveServerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveServerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveServerMethod "getAsyncContext" o = ServerGetAsyncContextMethodInfo
ResolveServerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveServerMethod "getListener" o = ServerGetListenerMethodInfo
ResolveServerMethod "getListeners" o = ServerGetListenersMethodInfo
ResolveServerMethod "getPort" o = ServerGetPortMethodInfo
ResolveServerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveServerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveServerMethod "getUris" o = ServerGetUrisMethodInfo
ResolveServerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveServerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveServerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveServerMethod "setSslCertFile" o = ServerSetSslCertFileMethodInfo
ResolveServerMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveServerMethod t Server, O.MethodInfo info Server p) => OL.IsLabel t (Server -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
type ServerRequestAbortedCallback =
Soup.Message.Message
-> Soup.ClientContext.ClientContext
-> IO ()
noServerRequestAbortedCallback :: Maybe ServerRequestAbortedCallback
noServerRequestAbortedCallback :: Maybe ServerRequestAbortedCallback
noServerRequestAbortedCallback = Maybe ServerRequestAbortedCallback
forall a. Maybe a
Nothing
type C_ServerRequestAbortedCallback =
Ptr () ->
Ptr Soup.Message.Message ->
Ptr Soup.ClientContext.ClientContext ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_ServerRequestAbortedCallback :: C_ServerRequestAbortedCallback -> IO (FunPtr C_ServerRequestAbortedCallback)
genClosure_ServerRequestAborted :: MonadIO m => ServerRequestAbortedCallback -> m (GClosure C_ServerRequestAbortedCallback)
genClosure_ServerRequestAborted :: ServerRequestAbortedCallback
-> m (GClosure C_ServerRequestAbortedCallback)
genClosure_ServerRequestAborted ServerRequestAbortedCallback
cb = IO (GClosure C_ServerRequestAbortedCallback)
-> m (GClosure C_ServerRequestAbortedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ServerRequestAbortedCallback)
-> m (GClosure C_ServerRequestAbortedCallback))
-> IO (GClosure C_ServerRequestAbortedCallback)
-> m (GClosure C_ServerRequestAbortedCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ServerRequestAbortedCallback
cb' = ServerRequestAbortedCallback -> C_ServerRequestAbortedCallback
wrap_ServerRequestAbortedCallback ServerRequestAbortedCallback
cb
C_ServerRequestAbortedCallback
-> IO (FunPtr C_ServerRequestAbortedCallback)
mk_ServerRequestAbortedCallback C_ServerRequestAbortedCallback
cb' IO (FunPtr C_ServerRequestAbortedCallback)
-> (FunPtr C_ServerRequestAbortedCallback
-> IO (GClosure C_ServerRequestAbortedCallback))
-> IO (GClosure C_ServerRequestAbortedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ServerRequestAbortedCallback
-> IO (GClosure C_ServerRequestAbortedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_ServerRequestAbortedCallback ::
ServerRequestAbortedCallback ->
C_ServerRequestAbortedCallback
wrap_ServerRequestAbortedCallback :: ServerRequestAbortedCallback -> C_ServerRequestAbortedCallback
wrap_ServerRequestAbortedCallback ServerRequestAbortedCallback
_cb Ptr ()
_ Ptr Message
message Ptr ClientContext
client Ptr ()
_ = do
Message
message' <- ((ManagedPtr Message -> Message) -> Ptr Message -> IO Message
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Message -> Message
Soup.Message.Message) Ptr Message
message
(ManagedPtr ClientContext -> ClientContext)
-> Ptr ClientContext -> (ClientContext -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
(ManagedPtr a -> a) -> Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient ManagedPtr ClientContext -> ClientContext
Soup.ClientContext.ClientContext Ptr ClientContext
client ((ClientContext -> IO ()) -> IO ())
-> (ClientContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ClientContext
client' -> do
ServerRequestAbortedCallback
_cb Message
message' ClientContext
client'
onServerRequestAborted :: (IsServer a, MonadIO m) => a -> ServerRequestAbortedCallback -> m SignalHandlerId
onServerRequestAborted :: a -> ServerRequestAbortedCallback -> m SignalHandlerId
onServerRequestAborted a
obj ServerRequestAbortedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ServerRequestAbortedCallback
cb' = ServerRequestAbortedCallback -> C_ServerRequestAbortedCallback
wrap_ServerRequestAbortedCallback ServerRequestAbortedCallback
cb
FunPtr C_ServerRequestAbortedCallback
cb'' <- C_ServerRequestAbortedCallback
-> IO (FunPtr C_ServerRequestAbortedCallback)
mk_ServerRequestAbortedCallback C_ServerRequestAbortedCallback
cb'
a
-> Text
-> FunPtr C_ServerRequestAbortedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"request-aborted" FunPtr C_ServerRequestAbortedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterServerRequestAborted :: (IsServer a, MonadIO m) => a -> ServerRequestAbortedCallback -> m SignalHandlerId
afterServerRequestAborted :: a -> ServerRequestAbortedCallback -> m SignalHandlerId
afterServerRequestAborted a
obj ServerRequestAbortedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ServerRequestAbortedCallback
cb' = ServerRequestAbortedCallback -> C_ServerRequestAbortedCallback
wrap_ServerRequestAbortedCallback ServerRequestAbortedCallback
cb
FunPtr C_ServerRequestAbortedCallback
cb'' <- C_ServerRequestAbortedCallback
-> IO (FunPtr C_ServerRequestAbortedCallback)
mk_ServerRequestAbortedCallback C_ServerRequestAbortedCallback
cb'
a
-> Text
-> FunPtr C_ServerRequestAbortedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"request-aborted" FunPtr C_ServerRequestAbortedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ServerRequestAbortedSignalInfo
instance SignalInfo ServerRequestAbortedSignalInfo where
type HaskellCallbackType ServerRequestAbortedSignalInfo = ServerRequestAbortedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_ServerRequestAbortedCallback cb
cb'' <- mk_ServerRequestAbortedCallback cb'
connectSignalFunPtr obj "request-aborted" cb'' connectMode detail
#endif
type ServerRequestFinishedCallback =
Soup.Message.Message
-> Soup.ClientContext.ClientContext
-> IO ()
noServerRequestFinishedCallback :: Maybe ServerRequestFinishedCallback
noServerRequestFinishedCallback :: Maybe ServerRequestAbortedCallback
noServerRequestFinishedCallback = Maybe ServerRequestAbortedCallback
forall a. Maybe a
Nothing
type C_ServerRequestFinishedCallback =
Ptr () ->
Ptr Soup.Message.Message ->
Ptr Soup.ClientContext.ClientContext ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_ServerRequestFinishedCallback :: C_ServerRequestFinishedCallback -> IO (FunPtr C_ServerRequestFinishedCallback)
genClosure_ServerRequestFinished :: MonadIO m => ServerRequestFinishedCallback -> m (GClosure C_ServerRequestFinishedCallback)
genClosure_ServerRequestFinished :: ServerRequestAbortedCallback
-> m (GClosure C_ServerRequestAbortedCallback)
genClosure_ServerRequestFinished ServerRequestAbortedCallback
cb = IO (GClosure C_ServerRequestAbortedCallback)
-> m (GClosure C_ServerRequestAbortedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ServerRequestAbortedCallback)
-> m (GClosure C_ServerRequestAbortedCallback))
-> IO (GClosure C_ServerRequestAbortedCallback)
-> m (GClosure C_ServerRequestAbortedCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ServerRequestAbortedCallback
cb' = ServerRequestAbortedCallback -> C_ServerRequestAbortedCallback
wrap_ServerRequestFinishedCallback ServerRequestAbortedCallback
cb
C_ServerRequestAbortedCallback
-> IO (FunPtr C_ServerRequestAbortedCallback)
mk_ServerRequestFinishedCallback C_ServerRequestAbortedCallback
cb' IO (FunPtr C_ServerRequestAbortedCallback)
-> (FunPtr C_ServerRequestAbortedCallback
-> IO (GClosure C_ServerRequestAbortedCallback))
-> IO (GClosure C_ServerRequestAbortedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ServerRequestAbortedCallback
-> IO (GClosure C_ServerRequestAbortedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_ServerRequestFinishedCallback ::
ServerRequestFinishedCallback ->
C_ServerRequestFinishedCallback
wrap_ServerRequestFinishedCallback :: ServerRequestAbortedCallback -> C_ServerRequestAbortedCallback
wrap_ServerRequestFinishedCallback ServerRequestAbortedCallback
_cb Ptr ()
_ Ptr Message
message Ptr ClientContext
client Ptr ()
_ = do
Message
message' <- ((ManagedPtr Message -> Message) -> Ptr Message -> IO Message
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Message -> Message
Soup.Message.Message) Ptr Message
message
(ManagedPtr ClientContext -> ClientContext)
-> Ptr ClientContext -> (ClientContext -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
(ManagedPtr a -> a) -> Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient ManagedPtr ClientContext -> ClientContext
Soup.ClientContext.ClientContext Ptr ClientContext
client ((ClientContext -> IO ()) -> IO ())
-> (ClientContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ClientContext
client' -> do
ServerRequestAbortedCallback
_cb Message
message' ClientContext
client'
onServerRequestFinished :: (IsServer a, MonadIO m) => a -> ServerRequestFinishedCallback -> m SignalHandlerId
onServerRequestFinished :: a -> ServerRequestAbortedCallback -> m SignalHandlerId
onServerRequestFinished a
obj ServerRequestAbortedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ServerRequestAbortedCallback
cb' = ServerRequestAbortedCallback -> C_ServerRequestAbortedCallback
wrap_ServerRequestFinishedCallback ServerRequestAbortedCallback
cb
FunPtr C_ServerRequestAbortedCallback
cb'' <- C_ServerRequestAbortedCallback
-> IO (FunPtr C_ServerRequestAbortedCallback)
mk_ServerRequestFinishedCallback C_ServerRequestAbortedCallback
cb'
a
-> Text
-> FunPtr C_ServerRequestAbortedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"request-finished" FunPtr C_ServerRequestAbortedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterServerRequestFinished :: (IsServer a, MonadIO m) => a -> ServerRequestFinishedCallback -> m SignalHandlerId
afterServerRequestFinished :: a -> ServerRequestAbortedCallback -> m SignalHandlerId
afterServerRequestFinished a
obj ServerRequestAbortedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ServerRequestAbortedCallback
cb' = ServerRequestAbortedCallback -> C_ServerRequestAbortedCallback
wrap_ServerRequestFinishedCallback ServerRequestAbortedCallback
cb
FunPtr C_ServerRequestAbortedCallback
cb'' <- C_ServerRequestAbortedCallback
-> IO (FunPtr C_ServerRequestAbortedCallback)
mk_ServerRequestFinishedCallback C_ServerRequestAbortedCallback
cb'
a
-> Text
-> FunPtr C_ServerRequestAbortedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"request-finished" FunPtr C_ServerRequestAbortedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ServerRequestFinishedSignalInfo
instance SignalInfo ServerRequestFinishedSignalInfo where
type HaskellCallbackType ServerRequestFinishedSignalInfo = ServerRequestFinishedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_ServerRequestFinishedCallback cb
cb'' <- mk_ServerRequestFinishedCallback cb'
connectSignalFunPtr obj "request-finished" cb'' connectMode detail
#endif
type ServerRequestReadCallback =
Soup.Message.Message
-> Soup.ClientContext.ClientContext
-> IO ()
noServerRequestReadCallback :: Maybe ServerRequestReadCallback
noServerRequestReadCallback :: Maybe ServerRequestAbortedCallback
noServerRequestReadCallback = Maybe ServerRequestAbortedCallback
forall a. Maybe a
Nothing
type C_ServerRequestReadCallback =
Ptr () ->
Ptr Soup.Message.Message ->
Ptr Soup.ClientContext.ClientContext ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_ServerRequestReadCallback :: C_ServerRequestReadCallback -> IO (FunPtr C_ServerRequestReadCallback)
genClosure_ServerRequestRead :: MonadIO m => ServerRequestReadCallback -> m (GClosure C_ServerRequestReadCallback)
genClosure_ServerRequestRead :: ServerRequestAbortedCallback
-> m (GClosure C_ServerRequestAbortedCallback)
genClosure_ServerRequestRead ServerRequestAbortedCallback
cb = IO (GClosure C_ServerRequestAbortedCallback)
-> m (GClosure C_ServerRequestAbortedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ServerRequestAbortedCallback)
-> m (GClosure C_ServerRequestAbortedCallback))
-> IO (GClosure C_ServerRequestAbortedCallback)
-> m (GClosure C_ServerRequestAbortedCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ServerRequestAbortedCallback
cb' = ServerRequestAbortedCallback -> C_ServerRequestAbortedCallback
wrap_ServerRequestReadCallback ServerRequestAbortedCallback
cb
C_ServerRequestAbortedCallback
-> IO (FunPtr C_ServerRequestAbortedCallback)
mk_ServerRequestReadCallback C_ServerRequestAbortedCallback
cb' IO (FunPtr C_ServerRequestAbortedCallback)
-> (FunPtr C_ServerRequestAbortedCallback
-> IO (GClosure C_ServerRequestAbortedCallback))
-> IO (GClosure C_ServerRequestAbortedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ServerRequestAbortedCallback
-> IO (GClosure C_ServerRequestAbortedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_ServerRequestReadCallback ::
ServerRequestReadCallback ->
C_ServerRequestReadCallback
wrap_ServerRequestReadCallback :: ServerRequestAbortedCallback -> C_ServerRequestAbortedCallback
wrap_ServerRequestReadCallback ServerRequestAbortedCallback
_cb Ptr ()
_ Ptr Message
message Ptr ClientContext
client Ptr ()
_ = do
Message
message' <- ((ManagedPtr Message -> Message) -> Ptr Message -> IO Message
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Message -> Message
Soup.Message.Message) Ptr Message
message
(ManagedPtr ClientContext -> ClientContext)
-> Ptr ClientContext -> (ClientContext -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
(ManagedPtr a -> a) -> Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient ManagedPtr ClientContext -> ClientContext
Soup.ClientContext.ClientContext Ptr ClientContext
client ((ClientContext -> IO ()) -> IO ())
-> (ClientContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ClientContext
client' -> do
ServerRequestAbortedCallback
_cb Message
message' ClientContext
client'
onServerRequestRead :: (IsServer a, MonadIO m) => a -> ServerRequestReadCallback -> m SignalHandlerId
onServerRequestRead :: a -> ServerRequestAbortedCallback -> m SignalHandlerId
onServerRequestRead a
obj ServerRequestAbortedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ServerRequestAbortedCallback
cb' = ServerRequestAbortedCallback -> C_ServerRequestAbortedCallback
wrap_ServerRequestReadCallback ServerRequestAbortedCallback
cb
FunPtr C_ServerRequestAbortedCallback
cb'' <- C_ServerRequestAbortedCallback
-> IO (FunPtr C_ServerRequestAbortedCallback)
mk_ServerRequestReadCallback C_ServerRequestAbortedCallback
cb'
a
-> Text
-> FunPtr C_ServerRequestAbortedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"request-read" FunPtr C_ServerRequestAbortedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterServerRequestRead :: (IsServer a, MonadIO m) => a -> ServerRequestReadCallback -> m SignalHandlerId
afterServerRequestRead :: a -> ServerRequestAbortedCallback -> m SignalHandlerId
afterServerRequestRead a
obj ServerRequestAbortedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ServerRequestAbortedCallback
cb' = ServerRequestAbortedCallback -> C_ServerRequestAbortedCallback
wrap_ServerRequestReadCallback ServerRequestAbortedCallback
cb
FunPtr C_ServerRequestAbortedCallback
cb'' <- C_ServerRequestAbortedCallback
-> IO (FunPtr C_ServerRequestAbortedCallback)
mk_ServerRequestReadCallback C_ServerRequestAbortedCallback
cb'
a
-> Text
-> FunPtr C_ServerRequestAbortedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"request-read" FunPtr C_ServerRequestAbortedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ServerRequestReadSignalInfo
instance SignalInfo ServerRequestReadSignalInfo where
type HaskellCallbackType ServerRequestReadSignalInfo = ServerRequestReadCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_ServerRequestReadCallback cb
cb'' <- mk_ServerRequestReadCallback cb'
connectSignalFunPtr obj "request-read" cb'' connectMode detail
#endif
type ServerRequestStartedCallback =
Soup.Message.Message
-> Soup.ClientContext.ClientContext
-> IO ()
noServerRequestStartedCallback :: Maybe ServerRequestStartedCallback
noServerRequestStartedCallback :: Maybe ServerRequestAbortedCallback
noServerRequestStartedCallback = Maybe ServerRequestAbortedCallback
forall a. Maybe a
Nothing
type C_ServerRequestStartedCallback =
Ptr () ->
Ptr Soup.Message.Message ->
Ptr Soup.ClientContext.ClientContext ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_ServerRequestStartedCallback :: C_ServerRequestStartedCallback -> IO (FunPtr C_ServerRequestStartedCallback)
genClosure_ServerRequestStarted :: MonadIO m => ServerRequestStartedCallback -> m (GClosure C_ServerRequestStartedCallback)
genClosure_ServerRequestStarted :: ServerRequestAbortedCallback
-> m (GClosure C_ServerRequestAbortedCallback)
genClosure_ServerRequestStarted ServerRequestAbortedCallback
cb = IO (GClosure C_ServerRequestAbortedCallback)
-> m (GClosure C_ServerRequestAbortedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ServerRequestAbortedCallback)
-> m (GClosure C_ServerRequestAbortedCallback))
-> IO (GClosure C_ServerRequestAbortedCallback)
-> m (GClosure C_ServerRequestAbortedCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ServerRequestAbortedCallback
cb' = ServerRequestAbortedCallback -> C_ServerRequestAbortedCallback
wrap_ServerRequestStartedCallback ServerRequestAbortedCallback
cb
C_ServerRequestAbortedCallback
-> IO (FunPtr C_ServerRequestAbortedCallback)
mk_ServerRequestStartedCallback C_ServerRequestAbortedCallback
cb' IO (FunPtr C_ServerRequestAbortedCallback)
-> (FunPtr C_ServerRequestAbortedCallback
-> IO (GClosure C_ServerRequestAbortedCallback))
-> IO (GClosure C_ServerRequestAbortedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ServerRequestAbortedCallback
-> IO (GClosure C_ServerRequestAbortedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_ServerRequestStartedCallback ::
ServerRequestStartedCallback ->
C_ServerRequestStartedCallback
wrap_ServerRequestStartedCallback :: ServerRequestAbortedCallback -> C_ServerRequestAbortedCallback
wrap_ServerRequestStartedCallback ServerRequestAbortedCallback
_cb Ptr ()
_ Ptr Message
message Ptr ClientContext
client Ptr ()
_ = do
Message
message' <- ((ManagedPtr Message -> Message) -> Ptr Message -> IO Message
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Message -> Message
Soup.Message.Message) Ptr Message
message
(ManagedPtr ClientContext -> ClientContext)
-> Ptr ClientContext -> (ClientContext -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
(ManagedPtr a -> a) -> Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient ManagedPtr ClientContext -> ClientContext
Soup.ClientContext.ClientContext Ptr ClientContext
client ((ClientContext -> IO ()) -> IO ())
-> (ClientContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ClientContext
client' -> do
ServerRequestAbortedCallback
_cb Message
message' ClientContext
client'
onServerRequestStarted :: (IsServer a, MonadIO m) => a -> ServerRequestStartedCallback -> m SignalHandlerId
onServerRequestStarted :: a -> ServerRequestAbortedCallback -> m SignalHandlerId
onServerRequestStarted a
obj ServerRequestAbortedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ServerRequestAbortedCallback
cb' = ServerRequestAbortedCallback -> C_ServerRequestAbortedCallback
wrap_ServerRequestStartedCallback ServerRequestAbortedCallback
cb
FunPtr C_ServerRequestAbortedCallback
cb'' <- C_ServerRequestAbortedCallback
-> IO (FunPtr C_ServerRequestAbortedCallback)
mk_ServerRequestStartedCallback C_ServerRequestAbortedCallback
cb'
a
-> Text
-> FunPtr C_ServerRequestAbortedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"request-started" FunPtr C_ServerRequestAbortedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterServerRequestStarted :: (IsServer a, MonadIO m) => a -> ServerRequestStartedCallback -> m SignalHandlerId
afterServerRequestStarted :: a -> ServerRequestAbortedCallback -> m SignalHandlerId
afterServerRequestStarted a
obj ServerRequestAbortedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ServerRequestAbortedCallback
cb' = ServerRequestAbortedCallback -> C_ServerRequestAbortedCallback
wrap_ServerRequestStartedCallback ServerRequestAbortedCallback
cb
FunPtr C_ServerRequestAbortedCallback
cb'' <- C_ServerRequestAbortedCallback
-> IO (FunPtr C_ServerRequestAbortedCallback)
mk_ServerRequestStartedCallback C_ServerRequestAbortedCallback
cb'
a
-> Text
-> FunPtr C_ServerRequestAbortedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"request-started" FunPtr C_ServerRequestAbortedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ServerRequestStartedSignalInfo
instance SignalInfo ServerRequestStartedSignalInfo where
type HaskellCallbackType ServerRequestStartedSignalInfo = ServerRequestStartedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_ServerRequestStartedCallback cb
cb'' <- mk_ServerRequestStartedCallback cb'
connectSignalFunPtr obj "request-started" cb'' connectMode detail
#endif
getServerAsyncContext :: (MonadIO m, IsServer o) => o -> m (Ptr ())
getServerAsyncContext :: o -> m (Ptr ())
getServerAsyncContext o
obj = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Ptr ())
forall a b. GObject a => a -> String -> IO (Ptr b)
B.Properties.getObjectPropertyPtr o
obj String
"async-context"
constructServerAsyncContext :: (IsServer o, MIO.MonadIO m) => Ptr () -> m (GValueConstruct o)
constructServerAsyncContext :: Ptr () -> m (GValueConstruct o)
constructServerAsyncContext Ptr ()
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Ptr () -> IO (GValueConstruct o)
forall b o. String -> Ptr b -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyPtr String
"async-context" Ptr ()
val
#if defined(ENABLE_OVERLOADING)
data ServerAsyncContextPropertyInfo
instance AttrInfo ServerAsyncContextPropertyInfo where
type AttrAllowedOps ServerAsyncContextPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ServerAsyncContextPropertyInfo = IsServer
type AttrSetTypeConstraint ServerAsyncContextPropertyInfo = (~) (Ptr ())
type AttrTransferTypeConstraint ServerAsyncContextPropertyInfo = (~) (Ptr ())
type AttrTransferType ServerAsyncContextPropertyInfo = Ptr ()
type AttrGetType ServerAsyncContextPropertyInfo = (Ptr ())
type AttrLabel ServerAsyncContextPropertyInfo = "async-context"
type AttrOrigin ServerAsyncContextPropertyInfo = Server
attrGet = getServerAsyncContext
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructServerAsyncContext
attrClear = undefined
#endif
getServerHttpAliases :: (MonadIO m, IsServer o) => o -> m (Maybe [T.Text])
getServerHttpAliases :: o -> m (Maybe [Text])
getServerHttpAliases o
obj = IO (Maybe [Text]) -> m (Maybe [Text])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [Text]) -> m (Maybe [Text]))
-> IO (Maybe [Text]) -> m (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe [Text])
forall a. GObject a => a -> String -> IO (Maybe [Text])
B.Properties.getObjectPropertyStringArray o
obj String
"http-aliases"
setServerHttpAliases :: (MonadIO m, IsServer o) => o -> [T.Text] -> m ()
setServerHttpAliases :: o -> [Text] -> m ()
setServerHttpAliases o
obj [Text]
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"http-aliases" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
val)
constructServerHttpAliases :: (IsServer o, MIO.MonadIO m) => [T.Text] -> m (GValueConstruct o)
constructServerHttpAliases :: [Text] -> m (GValueConstruct o)
constructServerHttpAliases [Text]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe [Text] -> IO (GValueConstruct o)
forall o. String -> Maybe [Text] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyStringArray String
"http-aliases" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
P.Just [Text]
val)
clearServerHttpAliases :: (MonadIO m, IsServer o) => o -> m ()
clearServerHttpAliases :: o -> m ()
clearServerHttpAliases o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"http-aliases" (Maybe [Text]
forall a. Maybe a
Nothing :: Maybe [T.Text])
#if defined(ENABLE_OVERLOADING)
data ServerHttpAliasesPropertyInfo
instance AttrInfo ServerHttpAliasesPropertyInfo where
type AttrAllowedOps ServerHttpAliasesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint ServerHttpAliasesPropertyInfo = IsServer
type AttrSetTypeConstraint ServerHttpAliasesPropertyInfo = (~) [T.Text]
type AttrTransferTypeConstraint ServerHttpAliasesPropertyInfo = (~) [T.Text]
type AttrTransferType ServerHttpAliasesPropertyInfo = [T.Text]
type AttrGetType ServerHttpAliasesPropertyInfo = (Maybe [T.Text])
type AttrLabel ServerHttpAliasesPropertyInfo = "http-aliases"
type AttrOrigin ServerHttpAliasesPropertyInfo = Server
attrGet = getServerHttpAliases
attrSet = setServerHttpAliases
attrTransfer _ v = do
return v
attrConstruct = constructServerHttpAliases
attrClear = clearServerHttpAliases
#endif
getServerHttpsAliases :: (MonadIO m, IsServer o) => o -> m (Maybe [T.Text])
getServerHttpsAliases :: o -> m (Maybe [Text])
getServerHttpsAliases o
obj = IO (Maybe [Text]) -> m (Maybe [Text])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [Text]) -> m (Maybe [Text]))
-> IO (Maybe [Text]) -> m (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe [Text])
forall a. GObject a => a -> String -> IO (Maybe [Text])
B.Properties.getObjectPropertyStringArray o
obj String
"https-aliases"
setServerHttpsAliases :: (MonadIO m, IsServer o) => o -> [T.Text] -> m ()
setServerHttpsAliases :: o -> [Text] -> m ()
setServerHttpsAliases o
obj [Text]
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"https-aliases" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
val)
constructServerHttpsAliases :: (IsServer o, MIO.MonadIO m) => [T.Text] -> m (GValueConstruct o)
constructServerHttpsAliases :: [Text] -> m (GValueConstruct o)
constructServerHttpsAliases [Text]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe [Text] -> IO (GValueConstruct o)
forall o. String -> Maybe [Text] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyStringArray String
"https-aliases" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
P.Just [Text]
val)
clearServerHttpsAliases :: (MonadIO m, IsServer o) => o -> m ()
clearServerHttpsAliases :: o -> m ()
clearServerHttpsAliases o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"https-aliases" (Maybe [Text]
forall a. Maybe a
Nothing :: Maybe [T.Text])
#if defined(ENABLE_OVERLOADING)
data ServerHttpsAliasesPropertyInfo
instance AttrInfo ServerHttpsAliasesPropertyInfo where
type AttrAllowedOps ServerHttpsAliasesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint ServerHttpsAliasesPropertyInfo = IsServer
type AttrSetTypeConstraint ServerHttpsAliasesPropertyInfo = (~) [T.Text]
type AttrTransferTypeConstraint ServerHttpsAliasesPropertyInfo = (~) [T.Text]
type AttrTransferType ServerHttpsAliasesPropertyInfo = [T.Text]
type AttrGetType ServerHttpsAliasesPropertyInfo = (Maybe [T.Text])
type AttrLabel ServerHttpsAliasesPropertyInfo = "https-aliases"
type AttrOrigin ServerHttpsAliasesPropertyInfo = Server
attrGet = getServerHttpsAliases
attrSet = setServerHttpsAliases
attrTransfer _ v = do
return v
attrConstruct = constructServerHttpsAliases
attrClear = clearServerHttpsAliases
#endif
getServerInterface :: (MonadIO m, IsServer o) => o -> m (Maybe Soup.Address.Address)
getServerInterface :: o -> m (Maybe Address)
getServerInterface o
obj = IO (Maybe Address) -> m (Maybe Address)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Address) -> m (Maybe Address))
-> IO (Maybe Address) -> m (Maybe Address)
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr Address -> Address) -> IO (Maybe Address)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"interface" ManagedPtr Address -> Address
Soup.Address.Address
constructServerInterface :: (IsServer o, MIO.MonadIO m, Soup.Address.IsAddress a) => a -> m (GValueConstruct o)
constructServerInterface :: a -> m (GValueConstruct o)
constructServerInterface a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"interface" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data ServerInterfacePropertyInfo
instance AttrInfo ServerInterfacePropertyInfo where
type AttrAllowedOps ServerInterfacePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint ServerInterfacePropertyInfo = IsServer
type AttrSetTypeConstraint ServerInterfacePropertyInfo = Soup.Address.IsAddress
type AttrTransferTypeConstraint ServerInterfacePropertyInfo = Soup.Address.IsAddress
type AttrTransferType ServerInterfacePropertyInfo = Soup.Address.Address
type AttrGetType ServerInterfacePropertyInfo = (Maybe Soup.Address.Address)
type AttrLabel ServerInterfacePropertyInfo = "interface"
type AttrOrigin ServerInterfacePropertyInfo = Server
attrGet = getServerInterface
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo Soup.Address.Address v
attrConstruct = constructServerInterface
attrClear = undefined
#endif
getServerPort :: (MonadIO m, IsServer o) => o -> m Word32
getServerPort :: o -> m Word32
getServerPort o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"port"
constructServerPort :: (IsServer o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructServerPort :: Word32 -> m (GValueConstruct o)
constructServerPort Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"port" Word32
val
#if defined(ENABLE_OVERLOADING)
data ServerPortPropertyInfo
instance AttrInfo ServerPortPropertyInfo where
type AttrAllowedOps ServerPortPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ServerPortPropertyInfo = IsServer
type AttrSetTypeConstraint ServerPortPropertyInfo = (~) Word32
type AttrTransferTypeConstraint ServerPortPropertyInfo = (~) Word32
type AttrTransferType ServerPortPropertyInfo = Word32
type AttrGetType ServerPortPropertyInfo = Word32
type AttrLabel ServerPortPropertyInfo = "port"
type AttrOrigin ServerPortPropertyInfo = Server
attrGet = getServerPort
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructServerPort
attrClear = undefined
#endif
getServerRawPaths :: (MonadIO m, IsServer o) => o -> m Bool
getServerRawPaths :: o -> m Bool
getServerRawPaths o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"raw-paths"
constructServerRawPaths :: (IsServer o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructServerRawPaths :: Bool -> m (GValueConstruct o)
constructServerRawPaths Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"raw-paths" Bool
val
#if defined(ENABLE_OVERLOADING)
data ServerRawPathsPropertyInfo
instance AttrInfo ServerRawPathsPropertyInfo where
type AttrAllowedOps ServerRawPathsPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ServerRawPathsPropertyInfo = IsServer
type AttrSetTypeConstraint ServerRawPathsPropertyInfo = (~) Bool
type AttrTransferTypeConstraint ServerRawPathsPropertyInfo = (~) Bool
type AttrTransferType ServerRawPathsPropertyInfo = Bool
type AttrGetType ServerRawPathsPropertyInfo = Bool
type AttrLabel ServerRawPathsPropertyInfo = "raw-paths"
type AttrOrigin ServerRawPathsPropertyInfo = Server
attrGet = getServerRawPaths
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructServerRawPaths
attrClear = undefined
#endif
getServerServerHeader :: (MonadIO m, IsServer o) => o -> m (Maybe T.Text)
o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"server-header"
setServerServerHeader :: (MonadIO m, IsServer o) => o -> T.Text -> m ()
o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"server-header" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructServerServerHeader :: (IsServer o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"server-header" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearServerServerHeader :: (MonadIO m, IsServer o) => o -> m ()
o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"server-header" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data ServerServerHeaderPropertyInfo
instance AttrInfo ServerServerHeaderPropertyInfo where
type AttrAllowedOps ServerServerHeaderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint ServerServerHeaderPropertyInfo = IsServer
type AttrSetTypeConstraint ServerServerHeaderPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint ServerServerHeaderPropertyInfo = (~) T.Text
type AttrTransferType ServerServerHeaderPropertyInfo = T.Text
type AttrGetType ServerServerHeaderPropertyInfo = (Maybe T.Text)
type AttrLabel ServerServerHeaderPropertyInfo = "server-header"
type AttrOrigin ServerServerHeaderPropertyInfo = Server
attrGet = getServerServerHeader
attrSet = setServerServerHeader
attrTransfer _ v = do
return v
attrConstruct = constructServerServerHeader
attrClear = clearServerServerHeader
#endif
getServerSslCertFile :: (MonadIO m, IsServer o) => o -> m (Maybe T.Text)
o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"ssl-cert-file"
constructServerSslCertFile :: (IsServer o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"ssl-cert-file" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data ServerSslCertFilePropertyInfo
instance AttrInfo ServerSslCertFilePropertyInfo where
type AttrAllowedOps ServerSslCertFilePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint ServerSslCertFilePropertyInfo = IsServer
type AttrSetTypeConstraint ServerSslCertFilePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint ServerSslCertFilePropertyInfo = (~) T.Text
type AttrTransferType ServerSslCertFilePropertyInfo = T.Text
type AttrGetType ServerSslCertFilePropertyInfo = (Maybe T.Text)
type AttrLabel ServerSslCertFilePropertyInfo = "ssl-cert-file"
type AttrOrigin ServerSslCertFilePropertyInfo = Server
attrGet = getServerSslCertFile
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructServerSslCertFile
attrClear = undefined
#endif
getServerSslKeyFile :: (MonadIO m, IsServer o) => o -> m (Maybe T.Text)
o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"ssl-key-file"
constructServerSslKeyFile :: (IsServer o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"ssl-key-file" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data ServerSslKeyFilePropertyInfo
instance AttrInfo ServerSslKeyFilePropertyInfo where
type AttrAllowedOps ServerSslKeyFilePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint ServerSslKeyFilePropertyInfo = IsServer
type AttrSetTypeConstraint ServerSslKeyFilePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint ServerSslKeyFilePropertyInfo = (~) T.Text
type AttrTransferType ServerSslKeyFilePropertyInfo = T.Text
type AttrGetType ServerSslKeyFilePropertyInfo = (Maybe T.Text)
type AttrLabel ServerSslKeyFilePropertyInfo = "ssl-key-file"
type AttrOrigin ServerSslKeyFilePropertyInfo = Server
attrGet = getServerSslKeyFile
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructServerSslKeyFile
attrClear = undefined
#endif
getServerTlsCertificate :: (MonadIO m, IsServer o) => o -> m (Maybe Gio.TlsCertificate.TlsCertificate)
getServerTlsCertificate :: o -> m (Maybe TlsCertificate)
getServerTlsCertificate o
obj = IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate))
-> IO (Maybe TlsCertificate) -> m (Maybe TlsCertificate)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr TlsCertificate -> TlsCertificate)
-> IO (Maybe TlsCertificate)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"tls-certificate" ManagedPtr TlsCertificate -> TlsCertificate
Gio.TlsCertificate.TlsCertificate
constructServerTlsCertificate :: (IsServer o, MIO.MonadIO m, Gio.TlsCertificate.IsTlsCertificate a) => a -> m (GValueConstruct o)
constructServerTlsCertificate :: a -> m (GValueConstruct o)
constructServerTlsCertificate a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"tls-certificate" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data ServerTlsCertificatePropertyInfo
instance AttrInfo ServerTlsCertificatePropertyInfo where
type AttrAllowedOps ServerTlsCertificatePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint ServerTlsCertificatePropertyInfo = IsServer
type AttrSetTypeConstraint ServerTlsCertificatePropertyInfo = Gio.TlsCertificate.IsTlsCertificate
type AttrTransferTypeConstraint ServerTlsCertificatePropertyInfo = Gio.TlsCertificate.IsTlsCertificate
type AttrTransferType ServerTlsCertificatePropertyInfo = Gio.TlsCertificate.TlsCertificate
type AttrGetType ServerTlsCertificatePropertyInfo = (Maybe Gio.TlsCertificate.TlsCertificate)
type AttrLabel ServerTlsCertificatePropertyInfo = "tls-certificate"
type AttrOrigin ServerTlsCertificatePropertyInfo = Server
attrGet = getServerTlsCertificate
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo Gio.TlsCertificate.TlsCertificate v
attrConstruct = constructServerTlsCertificate
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Server
type instance O.AttributeList Server = ServerAttributeList
type ServerAttributeList = ('[ '("asyncContext", ServerAsyncContextPropertyInfo), '("httpAliases", ServerHttpAliasesPropertyInfo), '("httpsAliases", ServerHttpsAliasesPropertyInfo), '("interface", ServerInterfacePropertyInfo), '("port", ServerPortPropertyInfo), '("rawPaths", ServerRawPathsPropertyInfo), '("serverHeader", ServerServerHeaderPropertyInfo), '("sslCertFile", ServerSslCertFilePropertyInfo), '("sslKeyFile", ServerSslKeyFilePropertyInfo), '("tlsCertificate", ServerTlsCertificatePropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
serverAsyncContext :: AttrLabelProxy "asyncContext"
serverAsyncContext = AttrLabelProxy
serverHttpAliases :: AttrLabelProxy "httpAliases"
serverHttpAliases = AttrLabelProxy
serverHttpsAliases :: AttrLabelProxy "httpsAliases"
serverHttpsAliases = AttrLabelProxy
serverInterface :: AttrLabelProxy "interface"
serverInterface = AttrLabelProxy
serverPort :: AttrLabelProxy "port"
serverPort = AttrLabelProxy
serverRawPaths :: AttrLabelProxy "rawPaths"
serverRawPaths = AttrLabelProxy
serverServerHeader :: AttrLabelProxy "serverHeader"
serverServerHeader = AttrLabelProxy
serverSslCertFile :: AttrLabelProxy "sslCertFile"
serverSslCertFile = AttrLabelProxy
serverSslKeyFile :: AttrLabelProxy "sslKeyFile"
serverSslKeyFile = AttrLabelProxy
serverTlsCertificate :: AttrLabelProxy "tlsCertificate"
serverTlsCertificate = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Server = ServerSignalList
type ServerSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo), '("requestAborted", ServerRequestAbortedSignalInfo), '("requestFinished", ServerRequestFinishedSignalInfo), '("requestRead", ServerRequestReadSignalInfo), '("requestStarted", ServerRequestStartedSignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "soup_server_accept_iostream" soup_server_accept_iostream ::
Ptr Server ->
Ptr Gio.IOStream.IOStream ->
Ptr Gio.SocketAddress.SocketAddress ->
Ptr Gio.SocketAddress.SocketAddress ->
Ptr (Ptr GError) ->
IO CInt
serverAcceptIostream ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a, Gio.IOStream.IsIOStream b, Gio.SocketAddress.IsSocketAddress c, Gio.SocketAddress.IsSocketAddress d) =>
a
-> b
-> Maybe (c)
-> Maybe (d)
-> m ()
serverAcceptIostream :: a -> b -> Maybe c -> Maybe d -> m ()
serverAcceptIostream a
server b
stream Maybe c
localAddr Maybe d
remoteAddr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr IOStream
stream' <- b -> IO (Ptr IOStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
stream
Ptr SocketAddress
maybeLocalAddr <- case Maybe c
localAddr of
Maybe c
Nothing -> Ptr SocketAddress -> IO (Ptr SocketAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketAddress
forall a. Ptr a
nullPtr
Just c
jLocalAddr -> do
Ptr SocketAddress
jLocalAddr' <- c -> IO (Ptr SocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jLocalAddr
Ptr SocketAddress -> IO (Ptr SocketAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketAddress
jLocalAddr'
Ptr SocketAddress
maybeRemoteAddr <- case Maybe d
remoteAddr of
Maybe d
Nothing -> Ptr SocketAddress -> IO (Ptr SocketAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketAddress
forall a. Ptr a
nullPtr
Just d
jRemoteAddr -> do
Ptr SocketAddress
jRemoteAddr' <- d -> IO (Ptr SocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr d
jRemoteAddr
Ptr SocketAddress -> IO (Ptr SocketAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SocketAddress
jRemoteAddr'
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Server
-> Ptr IOStream
-> Ptr SocketAddress
-> Ptr SocketAddress
-> Ptr (Ptr GError)
-> IO CInt
soup_server_accept_iostream Ptr Server
server' Ptr IOStream
stream' Ptr SocketAddress
maybeLocalAddr Ptr SocketAddress
maybeRemoteAddr
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
stream
Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
localAddr c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Maybe d -> (d -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe d
remoteAddr d -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data ServerAcceptIostreamMethodInfo
instance (signature ~ (b -> Maybe (c) -> Maybe (d) -> m ()), MonadIO m, IsServer a, Gio.IOStream.IsIOStream b, Gio.SocketAddress.IsSocketAddress c, Gio.SocketAddress.IsSocketAddress d) => O.MethodInfo ServerAcceptIostreamMethodInfo a signature where
overloadedMethod = serverAcceptIostream
#endif
foreign import ccall "soup_server_add_auth_domain" soup_server_add_auth_domain ::
Ptr Server ->
Ptr Soup.AuthDomain.AuthDomain ->
IO ()
serverAddAuthDomain ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a, Soup.AuthDomain.IsAuthDomain b) =>
a
-> b
-> m ()
serverAddAuthDomain :: a -> b -> m ()
serverAddAuthDomain a
server b
authDomain = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr AuthDomain
authDomain' <- b -> IO (Ptr AuthDomain)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
authDomain
Ptr Server -> Ptr AuthDomain -> IO ()
soup_server_add_auth_domain Ptr Server
server' Ptr AuthDomain
authDomain'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
authDomain
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ServerAddAuthDomainMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsServer a, Soup.AuthDomain.IsAuthDomain b) => O.MethodInfo ServerAddAuthDomainMethodInfo a signature where
overloadedMethod = serverAddAuthDomain
#endif
foreign import ccall "soup_server_add_early_handler" soup_server_add_early_handler ::
Ptr Server ->
CString ->
FunPtr Soup.Callbacks.C_ServerCallback ->
Ptr () ->
FunPtr GLib.Callbacks.C_DestroyNotify ->
IO ()
serverAddEarlyHandler ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> Maybe (T.Text)
-> Soup.Callbacks.ServerCallback
-> m ()
serverAddEarlyHandler :: a -> Maybe Text -> ServerCallback -> m ()
serverAddEarlyHandler a
server Maybe Text
path ServerCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr CChar
maybePath <- case Maybe Text
path of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jPath -> do
Ptr CChar
jPath' <- Text -> IO (Ptr CChar)
textToCString Text
jPath
Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jPath'
FunPtr C_ServerCallback
callback' <- C_ServerCallback -> IO (FunPtr C_ServerCallback)
Soup.Callbacks.mk_ServerCallback (Maybe (Ptr (FunPtr C_ServerCallback))
-> ServerCallback_WithClosures -> C_ServerCallback
Soup.Callbacks.wrap_ServerCallback Maybe (Ptr (FunPtr C_ServerCallback))
forall a. Maybe a
Nothing (ServerCallback -> ServerCallback_WithClosures
Soup.Callbacks.drop_closures_ServerCallback ServerCallback
callback))
let userData :: Ptr ()
userData = FunPtr C_ServerCallback -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_ServerCallback
callback'
let destroy :: FunPtr (Ptr a -> IO ())
destroy = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
safeFreeFunPtrPtr
Ptr Server
-> Ptr CChar
-> FunPtr C_ServerCallback
-> Ptr ()
-> FunPtr C_DestroyNotify
-> IO ()
soup_server_add_early_handler Ptr Server
server' Ptr CChar
maybePath FunPtr C_ServerCallback
callback' Ptr ()
userData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
destroy
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybePath
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ServerAddEarlyHandlerMethodInfo
instance (signature ~ (Maybe (T.Text) -> Soup.Callbacks.ServerCallback -> m ()), MonadIO m, IsServer a) => O.MethodInfo ServerAddEarlyHandlerMethodInfo a signature where
overloadedMethod = serverAddEarlyHandler
#endif
foreign import ccall "soup_server_add_handler" soup_server_add_handler ::
Ptr Server ->
CString ->
FunPtr Soup.Callbacks.C_ServerCallback ->
Ptr () ->
FunPtr GLib.Callbacks.C_DestroyNotify ->
IO ()
serverAddHandler ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> Maybe (T.Text)
-> Soup.Callbacks.ServerCallback
-> m ()
serverAddHandler :: a -> Maybe Text -> ServerCallback -> m ()
serverAddHandler a
server Maybe Text
path ServerCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr CChar
maybePath <- case Maybe Text
path of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jPath -> do
Ptr CChar
jPath' <- Text -> IO (Ptr CChar)
textToCString Text
jPath
Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jPath'
FunPtr C_ServerCallback
callback' <- C_ServerCallback -> IO (FunPtr C_ServerCallback)
Soup.Callbacks.mk_ServerCallback (Maybe (Ptr (FunPtr C_ServerCallback))
-> ServerCallback_WithClosures -> C_ServerCallback
Soup.Callbacks.wrap_ServerCallback Maybe (Ptr (FunPtr C_ServerCallback))
forall a. Maybe a
Nothing (ServerCallback -> ServerCallback_WithClosures
Soup.Callbacks.drop_closures_ServerCallback ServerCallback
callback))
let userData :: Ptr ()
userData = FunPtr C_ServerCallback -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_ServerCallback
callback'
let destroy :: FunPtr (Ptr a -> IO ())
destroy = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
safeFreeFunPtrPtr
Ptr Server
-> Ptr CChar
-> FunPtr C_ServerCallback
-> Ptr ()
-> FunPtr C_DestroyNotify
-> IO ()
soup_server_add_handler Ptr Server
server' Ptr CChar
maybePath FunPtr C_ServerCallback
callback' Ptr ()
userData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
destroy
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybePath
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ServerAddHandlerMethodInfo
instance (signature ~ (Maybe (T.Text) -> Soup.Callbacks.ServerCallback -> m ()), MonadIO m, IsServer a) => O.MethodInfo ServerAddHandlerMethodInfo a signature where
overloadedMethod = serverAddHandler
#endif
foreign import ccall "soup_server_add_websocket_extension" soup_server_add_websocket_extension ::
Ptr Server ->
CGType ->
IO ()
serverAddWebsocketExtension ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> GType
-> m ()
serverAddWebsocketExtension :: a -> GType -> m ()
serverAddWebsocketExtension a
server GType
extensionType = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
let extensionType' :: CGType
extensionType' = GType -> CGType
gtypeToCGType GType
extensionType
Ptr Server -> CGType -> IO ()
soup_server_add_websocket_extension Ptr Server
server' CGType
extensionType'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ServerAddWebsocketExtensionMethodInfo
instance (signature ~ (GType -> m ()), MonadIO m, IsServer a) => O.MethodInfo ServerAddWebsocketExtensionMethodInfo a signature where
overloadedMethod = serverAddWebsocketExtension
#endif
foreign import ccall "soup_server_add_websocket_handler" soup_server_add_websocket_handler ::
Ptr Server ->
CString ->
CString ->
Ptr CString ->
FunPtr Soup.Callbacks.C_ServerWebsocketCallback ->
Ptr () ->
FunPtr GLib.Callbacks.C_DestroyNotify ->
IO ()
serverAddWebsocketHandler ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> Maybe (T.Text)
-> Maybe (T.Text)
-> Maybe ([T.Text])
-> Soup.Callbacks.ServerWebsocketCallback
-> m ()
serverAddWebsocketHandler :: a
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> ServerWebsocketCallback
-> m ()
serverAddWebsocketHandler a
server Maybe Text
path Maybe Text
origin Maybe [Text]
protocols ServerWebsocketCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr CChar
maybePath <- case Maybe Text
path of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jPath -> do
Ptr CChar
jPath' <- Text -> IO (Ptr CChar)
textToCString Text
jPath
Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jPath'
Ptr CChar
maybeOrigin <- case Maybe Text
origin of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jOrigin -> do
Ptr CChar
jOrigin' <- Text -> IO (Ptr CChar)
textToCString Text
jOrigin
Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jOrigin'
Ptr (Ptr CChar)
maybeProtocols <- case Maybe [Text]
protocols of
Maybe [Text]
Nothing -> Ptr (Ptr CChar) -> IO (Ptr (Ptr CChar))
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr CChar)
forall a. Ptr a
nullPtr
Just [Text]
jProtocols -> do
Ptr (Ptr CChar)
jProtocols' <- [Text] -> IO (Ptr (Ptr CChar))
packZeroTerminatedUTF8CArray [Text]
jProtocols
Ptr (Ptr CChar) -> IO (Ptr (Ptr CChar))
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr CChar)
jProtocols'
FunPtr C_ServerWebsocketCallback
callback' <- C_ServerWebsocketCallback -> IO (FunPtr C_ServerWebsocketCallback)
Soup.Callbacks.mk_ServerWebsocketCallback (Maybe (Ptr (FunPtr C_ServerWebsocketCallback))
-> ServerWebsocketCallback_WithClosures
-> C_ServerWebsocketCallback
Soup.Callbacks.wrap_ServerWebsocketCallback Maybe (Ptr (FunPtr C_ServerWebsocketCallback))
forall a. Maybe a
Nothing (ServerWebsocketCallback -> ServerWebsocketCallback_WithClosures
Soup.Callbacks.drop_closures_ServerWebsocketCallback ServerWebsocketCallback
callback))
let userData :: Ptr ()
userData = FunPtr C_ServerWebsocketCallback -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_ServerWebsocketCallback
callback'
let destroy :: FunPtr (Ptr a -> IO ())
destroy = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
safeFreeFunPtrPtr
Ptr Server
-> Ptr CChar
-> Ptr CChar
-> Ptr (Ptr CChar)
-> FunPtr C_ServerWebsocketCallback
-> Ptr ()
-> FunPtr C_DestroyNotify
-> IO ()
soup_server_add_websocket_handler Ptr Server
server' Ptr CChar
maybePath Ptr CChar
maybeOrigin Ptr (Ptr CChar)
maybeProtocols FunPtr C_ServerWebsocketCallback
callback' Ptr ()
userData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
destroy
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybePath
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeOrigin
(Ptr CChar -> IO ()) -> Ptr (Ptr CChar) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
maybeProtocols
Ptr (Ptr CChar) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
maybeProtocols
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ServerAddWebsocketHandlerMethodInfo
instance (signature ~ (Maybe (T.Text) -> Maybe (T.Text) -> Maybe ([T.Text]) -> Soup.Callbacks.ServerWebsocketCallback -> m ()), MonadIO m, IsServer a) => O.MethodInfo ServerAddWebsocketHandlerMethodInfo a signature where
overloadedMethod = serverAddWebsocketHandler
#endif
foreign import ccall "soup_server_disconnect" soup_server_disconnect ::
Ptr Server ->
IO ()
serverDisconnect ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> m ()
serverDisconnect :: a -> m ()
serverDisconnect a
server = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr Server -> IO ()
soup_server_disconnect Ptr Server
server'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ServerDisconnectMethodInfo
instance (signature ~ (m ()), MonadIO m, IsServer a) => O.MethodInfo ServerDisconnectMethodInfo a signature where
overloadedMethod = serverDisconnect
#endif
foreign import ccall "soup_server_get_async_context" soup_server_get_async_context ::
Ptr Server ->
IO (Ptr GLib.MainContext.MainContext)
{-# DEPRECATED serverGetAsyncContext ["If you are using 'GI.Soup.Objects.Server.serverListen', etc, then","the server listens on the thread-default t'GI.GLib.Structs.MainContext.MainContext', and this","property is ignored."] #-}
serverGetAsyncContext ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> m (Maybe GLib.MainContext.MainContext)
serverGetAsyncContext :: a -> m (Maybe MainContext)
serverGetAsyncContext a
server = IO (Maybe MainContext) -> m (Maybe MainContext)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe MainContext) -> m (Maybe MainContext))
-> IO (Maybe MainContext) -> m (Maybe MainContext)
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr MainContext
result <- Ptr Server -> IO (Ptr MainContext)
soup_server_get_async_context Ptr Server
server'
Maybe MainContext
maybeResult <- Ptr MainContext
-> (Ptr MainContext -> IO MainContext) -> IO (Maybe MainContext)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr MainContext
result ((Ptr MainContext -> IO MainContext) -> IO (Maybe MainContext))
-> (Ptr MainContext -> IO MainContext) -> IO (Maybe MainContext)
forall a b. (a -> b) -> a -> b
$ \Ptr MainContext
result' -> do
MainContext
result'' <- ((ManagedPtr MainContext -> MainContext)
-> Ptr MainContext -> IO MainContext
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr MainContext -> MainContext
GLib.MainContext.MainContext) Ptr MainContext
result'
MainContext -> IO MainContext
forall (m :: * -> *) a. Monad m => a -> m a
return MainContext
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
Maybe MainContext -> IO (Maybe MainContext)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MainContext
maybeResult
#if defined(ENABLE_OVERLOADING)
data ServerGetAsyncContextMethodInfo
instance (signature ~ (m (Maybe GLib.MainContext.MainContext)), MonadIO m, IsServer a) => O.MethodInfo ServerGetAsyncContextMethodInfo a signature where
overloadedMethod = serverGetAsyncContext
#endif
foreign import ccall "soup_server_get_listener" soup_server_get_listener ::
Ptr Server ->
IO (Ptr Soup.Socket.Socket)
{-# DEPRECATED serverGetListener ["If you are using 'GI.Soup.Objects.Server.serverListen', etc, then use","'GI.Soup.Objects.Server.serverGetListeners' to get a list of all listening sockets,","but note that that function returns @/GSockets/@, not @/SoupSockets/@."] #-}
serverGetListener ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> m Soup.Socket.Socket
serverGetListener :: a -> m Socket
serverGetListener a
server = IO Socket -> m Socket
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Socket -> m Socket) -> IO Socket -> m Socket
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr Socket
result <- Ptr Server -> IO (Ptr Socket)
soup_server_get_listener Ptr Server
server'
Text -> Ptr Socket -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"serverGetListener" Ptr Socket
result
Socket
result' <- ((ManagedPtr Socket -> Socket) -> Ptr Socket -> IO Socket
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Socket -> Socket
Soup.Socket.Socket) Ptr Socket
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
Socket -> IO Socket
forall (m :: * -> *) a. Monad m => a -> m a
return Socket
result'
#if defined(ENABLE_OVERLOADING)
data ServerGetListenerMethodInfo
instance (signature ~ (m Soup.Socket.Socket), MonadIO m, IsServer a) => O.MethodInfo ServerGetListenerMethodInfo a signature where
overloadedMethod = serverGetListener
#endif
foreign import ccall "soup_server_get_listeners" soup_server_get_listeners ::
Ptr Server ->
IO (Ptr (GSList (Ptr Gio.Socket.Socket)))
serverGetListeners ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> m [Gio.Socket.Socket]
serverGetListeners :: a -> m [Socket]
serverGetListeners a
server = IO [Socket] -> m [Socket]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Socket] -> m [Socket]) -> IO [Socket] -> m [Socket]
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr (GSList (Ptr Socket))
result <- Ptr Server -> IO (Ptr (GSList (Ptr Socket)))
soup_server_get_listeners Ptr Server
server'
[Ptr Socket]
result' <- Ptr (GSList (Ptr Socket)) -> IO [Ptr Socket]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr Socket))
result
[Socket]
result'' <- (Ptr Socket -> IO Socket) -> [Ptr Socket] -> IO [Socket]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Socket -> Socket) -> Ptr Socket -> IO Socket
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Socket -> Socket
Gio.Socket.Socket) [Ptr Socket]
result'
Ptr (GSList (Ptr Socket)) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free Ptr (GSList (Ptr Socket))
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
[Socket] -> IO [Socket]
forall (m :: * -> *) a. Monad m => a -> m a
return [Socket]
result''
#if defined(ENABLE_OVERLOADING)
data ServerGetListenersMethodInfo
instance (signature ~ (m [Gio.Socket.Socket]), MonadIO m, IsServer a) => O.MethodInfo ServerGetListenersMethodInfo a signature where
overloadedMethod = serverGetListeners
#endif
foreign import ccall "soup_server_get_port" soup_server_get_port ::
Ptr Server ->
IO Word32
{-# DEPRECATED serverGetPort ["If you are using 'GI.Soup.Objects.Server.serverListen', etc, then use","'GI.Soup.Objects.Server.serverGetUris' to get a list of all listening addresses."] #-}
serverGetPort ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> m Word32
serverGetPort :: a -> m Word32
serverGetPort a
server = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Word32
result <- Ptr Server -> IO Word32
soup_server_get_port Ptr Server
server'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data ServerGetPortMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsServer a) => O.MethodInfo ServerGetPortMethodInfo a signature where
overloadedMethod = serverGetPort
#endif
foreign import ccall "soup_server_get_uris" soup_server_get_uris ::
Ptr Server ->
IO (Ptr (GSList (Ptr Soup.URI.URI)))
serverGetUris ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> m [Soup.URI.URI]
serverGetUris :: a -> m [URI]
serverGetUris a
server = IO [URI] -> m [URI]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [URI] -> m [URI]) -> IO [URI] -> m [URI]
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr (GSList (Ptr URI))
result <- Ptr Server -> IO (Ptr (GSList (Ptr URI)))
soup_server_get_uris Ptr Server
server'
[Ptr URI]
result' <- Ptr (GSList (Ptr URI)) -> IO [Ptr URI]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr URI))
result
[URI]
result'' <- (Ptr URI -> IO URI) -> [Ptr URI] -> IO [URI]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr URI -> URI) -> Ptr URI -> IO URI
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr URI -> URI
Soup.URI.URI) [Ptr URI]
result'
Ptr (GSList (Ptr URI)) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free Ptr (GSList (Ptr URI))
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
[URI] -> IO [URI]
forall (m :: * -> *) a. Monad m => a -> m a
return [URI]
result''
#if defined(ENABLE_OVERLOADING)
data ServerGetUrisMethodInfo
instance (signature ~ (m [Soup.URI.URI]), MonadIO m, IsServer a) => O.MethodInfo ServerGetUrisMethodInfo a signature where
overloadedMethod = serverGetUris
#endif
foreign import ccall "soup_server_is_https" soup_server_is_https ::
Ptr Server ->
IO CInt
serverIsHttps ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> m Bool
serverIsHttps :: a -> m Bool
serverIsHttps a
server = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
CInt
result <- Ptr Server -> IO CInt
soup_server_is_https Ptr Server
server'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ServerIsHttpsMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsServer a) => O.MethodInfo ServerIsHttpsMethodInfo a signature where
overloadedMethod = serverIsHttps
#endif
foreign import ccall "soup_server_listen" soup_server_listen ::
Ptr Server ->
Ptr Gio.SocketAddress.SocketAddress ->
CUInt ->
Ptr (Ptr GError) ->
IO CInt
serverListen ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a, Gio.SocketAddress.IsSocketAddress b) =>
a
-> b
-> [Soup.Flags.ServerListenOptions]
-> m ()
serverListen :: a -> b -> [ServerListenOptions] -> m ()
serverListen a
server b
address [ServerListenOptions]
options = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr SocketAddress
address' <- b -> IO (Ptr SocketAddress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
address
let options' :: CUInt
options' = [ServerListenOptions] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ServerListenOptions]
options
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Server
-> Ptr SocketAddress -> CUInt -> Ptr (Ptr GError) -> IO CInt
soup_server_listen Ptr Server
server' Ptr SocketAddress
address' CUInt
options'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
address
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data ServerListenMethodInfo
instance (signature ~ (b -> [Soup.Flags.ServerListenOptions] -> m ()), MonadIO m, IsServer a, Gio.SocketAddress.IsSocketAddress b) => O.MethodInfo ServerListenMethodInfo a signature where
overloadedMethod = serverListen
#endif
foreign import ccall "soup_server_listen_all" soup_server_listen_all ::
Ptr Server ->
Word32 ->
CUInt ->
Ptr (Ptr GError) ->
IO CInt
serverListenAll ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> Word32
-> [Soup.Flags.ServerListenOptions]
-> m ()
serverListenAll :: a -> Word32 -> [ServerListenOptions] -> m ()
serverListenAll a
server Word32
port [ServerListenOptions]
options = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
let options' :: CUInt
options' = [ServerListenOptions] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ServerListenOptions]
options
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Server -> Word32 -> CUInt -> Ptr (Ptr GError) -> IO CInt
soup_server_listen_all Ptr Server
server' Word32
port CUInt
options'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data ServerListenAllMethodInfo
instance (signature ~ (Word32 -> [Soup.Flags.ServerListenOptions] -> m ()), MonadIO m, IsServer a) => O.MethodInfo ServerListenAllMethodInfo a signature where
overloadedMethod = serverListenAll
#endif
foreign import ccall "soup_server_listen_fd" soup_server_listen_fd ::
Ptr Server ->
Int32 ->
CUInt ->
Ptr (Ptr GError) ->
IO CInt
serverListenFd ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> Int32
-> [Soup.Flags.ServerListenOptions]
-> m ()
serverListenFd :: a -> Int32 -> [ServerListenOptions] -> m ()
serverListenFd a
server Int32
fd [ServerListenOptions]
options = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
let options' :: CUInt
options' = [ServerListenOptions] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ServerListenOptions]
options
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Server -> Int32 -> CUInt -> Ptr (Ptr GError) -> IO CInt
soup_server_listen_fd Ptr Server
server' Int32
fd CUInt
options'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data ServerListenFdMethodInfo
instance (signature ~ (Int32 -> [Soup.Flags.ServerListenOptions] -> m ()), MonadIO m, IsServer a) => O.MethodInfo ServerListenFdMethodInfo a signature where
overloadedMethod = serverListenFd
#endif
foreign import ccall "soup_server_listen_local" soup_server_listen_local ::
Ptr Server ->
Word32 ->
CUInt ->
Ptr (Ptr GError) ->
IO CInt
serverListenLocal ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> Word32
-> [Soup.Flags.ServerListenOptions]
-> m ()
serverListenLocal :: a -> Word32 -> [ServerListenOptions] -> m ()
serverListenLocal a
server Word32
port [ServerListenOptions]
options = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
let options' :: CUInt
options' = [ServerListenOptions] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ServerListenOptions]
options
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Server -> Word32 -> CUInt -> Ptr (Ptr GError) -> IO CInt
soup_server_listen_local Ptr Server
server' Word32
port CUInt
options'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data ServerListenLocalMethodInfo
instance (signature ~ (Word32 -> [Soup.Flags.ServerListenOptions] -> m ()), MonadIO m, IsServer a) => O.MethodInfo ServerListenLocalMethodInfo a signature where
overloadedMethod = serverListenLocal
#endif
foreign import ccall "soup_server_listen_socket" soup_server_listen_socket ::
Ptr Server ->
Ptr Gio.Socket.Socket ->
CUInt ->
Ptr (Ptr GError) ->
IO CInt
serverListenSocket ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a, Gio.Socket.IsSocket b) =>
a
-> b
-> [Soup.Flags.ServerListenOptions]
-> m ()
serverListenSocket :: a -> b -> [ServerListenOptions] -> m ()
serverListenSocket a
server b
socket [ServerListenOptions]
options = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr Socket
socket' <- b -> IO (Ptr Socket)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
socket
let options' :: CUInt
options' = [ServerListenOptions] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ServerListenOptions]
options
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Server -> Ptr Socket -> CUInt -> Ptr (Ptr GError) -> IO CInt
soup_server_listen_socket Ptr Server
server' Ptr Socket
socket' CUInt
options'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
socket
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data ServerListenSocketMethodInfo
instance (signature ~ (b -> [Soup.Flags.ServerListenOptions] -> m ()), MonadIO m, IsServer a, Gio.Socket.IsSocket b) => O.MethodInfo ServerListenSocketMethodInfo a signature where
overloadedMethod = serverListenSocket
#endif
foreign import ccall "soup_server_pause_message" soup_server_pause_message ::
Ptr Server ->
Ptr Soup.Message.Message ->
IO ()
serverPauseMessage ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a, Soup.Message.IsMessage b) =>
a
-> b
-> m ()
serverPauseMessage :: a -> b -> m ()
serverPauseMessage a
server b
msg = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr Message
msg' <- b -> IO (Ptr Message)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
msg
Ptr Server -> Ptr Message -> IO ()
soup_server_pause_message Ptr Server
server' Ptr Message
msg'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
msg
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ServerPauseMessageMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsServer a, Soup.Message.IsMessage b) => O.MethodInfo ServerPauseMessageMethodInfo a signature where
overloadedMethod = serverPauseMessage
#endif
foreign import ccall "soup_server_quit" soup_server_quit ::
Ptr Server ->
IO ()
{-# DEPRECATED serverQuit ["When using 'GI.Soup.Objects.Server.serverListen', etc, the server will","always listen for connections, and will process them whenever the","thread-default t'GI.GLib.Structs.MainContext.MainContext' is running."] #-}
serverQuit ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> m ()
serverQuit :: a -> m ()
serverQuit a
server = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr Server -> IO ()
soup_server_quit Ptr Server
server'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ServerQuitMethodInfo
instance (signature ~ (m ()), MonadIO m, IsServer a) => O.MethodInfo ServerQuitMethodInfo a signature where
overloadedMethod = serverQuit
#endif
foreign import ccall "soup_server_remove_auth_domain" soup_server_remove_auth_domain ::
Ptr Server ->
Ptr Soup.AuthDomain.AuthDomain ->
IO ()
serverRemoveAuthDomain ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a, Soup.AuthDomain.IsAuthDomain b) =>
a
-> b
-> m ()
serverRemoveAuthDomain :: a -> b -> m ()
serverRemoveAuthDomain a
server b
authDomain = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr AuthDomain
authDomain' <- b -> IO (Ptr AuthDomain)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
authDomain
Ptr Server -> Ptr AuthDomain -> IO ()
soup_server_remove_auth_domain Ptr Server
server' Ptr AuthDomain
authDomain'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
authDomain
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ServerRemoveAuthDomainMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsServer a, Soup.AuthDomain.IsAuthDomain b) => O.MethodInfo ServerRemoveAuthDomainMethodInfo a signature where
overloadedMethod = serverRemoveAuthDomain
#endif
foreign import ccall "soup_server_remove_handler" soup_server_remove_handler ::
Ptr Server ->
CString ->
IO ()
serverRemoveHandler ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> T.Text
-> m ()
serverRemoveHandler :: a -> Text -> m ()
serverRemoveHandler a
server Text
path = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr CChar
path' <- Text -> IO (Ptr CChar)
textToCString Text
path
Ptr Server -> Ptr CChar -> IO ()
soup_server_remove_handler Ptr Server
server' Ptr CChar
path'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
path'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ServerRemoveHandlerMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsServer a) => O.MethodInfo ServerRemoveHandlerMethodInfo a signature where
overloadedMethod = serverRemoveHandler
#endif
foreign import ccall "soup_server_remove_websocket_extension" soup_server_remove_websocket_extension ::
Ptr Server ->
CGType ->
IO ()
serverRemoveWebsocketExtension ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> GType
-> m ()
serverRemoveWebsocketExtension :: a -> GType -> m ()
serverRemoveWebsocketExtension a
server GType
extensionType = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
let extensionType' :: CGType
extensionType' = GType -> CGType
gtypeToCGType GType
extensionType
Ptr Server -> CGType -> IO ()
soup_server_remove_websocket_extension Ptr Server
server' CGType
extensionType'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ServerRemoveWebsocketExtensionMethodInfo
instance (signature ~ (GType -> m ()), MonadIO m, IsServer a) => O.MethodInfo ServerRemoveWebsocketExtensionMethodInfo a signature where
overloadedMethod = serverRemoveWebsocketExtension
#endif
foreign import ccall "soup_server_run" soup_server_run ::
Ptr Server ->
IO ()
{-# DEPRECATED serverRun ["When using 'GI.Soup.Objects.Server.serverListen', etc, the server will","always listen for connections, and will process them whenever the","thread-default t'GI.GLib.Structs.MainContext.MainContext' is running."] #-}
serverRun ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> m ()
serverRun :: a -> m ()
serverRun a
server = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr Server -> IO ()
soup_server_run Ptr Server
server'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ServerRunMethodInfo
instance (signature ~ (m ()), MonadIO m, IsServer a) => O.MethodInfo ServerRunMethodInfo a signature where
overloadedMethod = serverRun
#endif
foreign import ccall "soup_server_run_async" soup_server_run_async ::
Ptr Server ->
IO ()
{-# DEPRECATED serverRunAsync ["When using 'GI.Soup.Objects.Server.serverListen', etc, the server will","always listen for connections, and will process them whenever the","thread-default t'GI.GLib.Structs.MainContext.MainContext' is running."] #-}
serverRunAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> m ()
serverRunAsync :: a -> m ()
serverRunAsync a
server = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr Server -> IO ()
soup_server_run_async Ptr Server
server'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ServerRunAsyncMethodInfo
instance (signature ~ (m ()), MonadIO m, IsServer a) => O.MethodInfo ServerRunAsyncMethodInfo a signature where
overloadedMethod = serverRunAsync
#endif
foreign import ccall "soup_server_set_ssl_cert_file" soup_server_set_ssl_cert_file ::
Ptr Server ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO CInt
serverSetSslCertFile ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a) =>
a
-> T.Text
-> T.Text
-> m ()
serverSetSslCertFile :: a -> Text -> Text -> m ()
serverSetSslCertFile a
server Text
sslCertFile Text
sslKeyFile = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr CChar
sslCertFile' <- Text -> IO (Ptr CChar)
textToCString Text
sslCertFile
Ptr CChar
sslKeyFile' <- Text -> IO (Ptr CChar)
textToCString Text
sslKeyFile
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Server -> Ptr CChar -> Ptr CChar -> Ptr (Ptr GError) -> IO CInt
soup_server_set_ssl_cert_file Ptr Server
server' Ptr CChar
sslCertFile' Ptr CChar
sslKeyFile'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
sslCertFile'
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
sslKeyFile'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
sslCertFile'
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
sslKeyFile'
)
#if defined(ENABLE_OVERLOADING)
data ServerSetSslCertFileMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ()), MonadIO m, IsServer a) => O.MethodInfo ServerSetSslCertFileMethodInfo a signature where
overloadedMethod = serverSetSslCertFile
#endif
foreign import ccall "soup_server_unpause_message" soup_server_unpause_message ::
Ptr Server ->
Ptr Soup.Message.Message ->
IO ()
serverUnpauseMessage ::
(B.CallStack.HasCallStack, MonadIO m, IsServer a, Soup.Message.IsMessage b) =>
a
-> b
-> m ()
serverUnpauseMessage :: a -> b -> m ()
serverUnpauseMessage a
server b
msg = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Server
server' <- a -> IO (Ptr Server)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
server
Ptr Message
msg' <- b -> IO (Ptr Message)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
msg
Ptr Server -> Ptr Message -> IO ()
soup_server_unpause_message Ptr Server
server' Ptr Message
msg'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
server
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
msg
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ServerUnpauseMessageMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsServer a, Soup.Message.IsMessage b) => O.MethodInfo ServerUnpauseMessageMethodInfo a signature where
overloadedMethod = serverUnpauseMessage
#endif