{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Soup.Objects.AuthDomainDigest
(
AuthDomainDigest(..) ,
IsAuthDomainDigest ,
toAuthDomainDigest ,
noAuthDomainDigest ,
#if defined(ENABLE_OVERLOADING)
ResolveAuthDomainDigestMethod ,
#endif
authDomainDigestEncodePassword ,
#if defined(ENABLE_OVERLOADING)
AuthDomainDigestSetAuthCallbackMethodInfo,
#endif
authDomainDigestSetAuthCallback ,
#if defined(ENABLE_OVERLOADING)
AuthDomainDigestAuthCallbackPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
authDomainDigestAuthCallback ,
#endif
clearAuthDomainDigestAuthCallback ,
constructAuthDomainDigestAuthCallback ,
getAuthDomainDigestAuthCallback ,
setAuthDomainDigestAuthCallback ,
#if defined(ENABLE_OVERLOADING)
AuthDomainDigestAuthDataPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
authDomainDigestAuthData ,
#endif
constructAuthDomainDigestAuthData ,
getAuthDomainDigestAuthData ,
setAuthDomainDigestAuthData ,
) 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.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 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.GObject.Objects.Object as GObject.Object
import qualified GI.Soup.Callbacks as Soup.Callbacks
import {-# SOURCE #-} qualified GI.Soup.Objects.AuthDomain as Soup.AuthDomain
newtype AuthDomainDigest = AuthDomainDigest (ManagedPtr AuthDomainDigest)
deriving (AuthDomainDigest -> AuthDomainDigest -> Bool
(AuthDomainDigest -> AuthDomainDigest -> Bool)
-> (AuthDomainDigest -> AuthDomainDigest -> Bool)
-> Eq AuthDomainDigest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthDomainDigest -> AuthDomainDigest -> Bool
$c/= :: AuthDomainDigest -> AuthDomainDigest -> Bool
== :: AuthDomainDigest -> AuthDomainDigest -> Bool
$c== :: AuthDomainDigest -> AuthDomainDigest -> Bool
Eq)
foreign import ccall "soup_auth_domain_digest_get_type"
c_soup_auth_domain_digest_get_type :: IO GType
instance GObject AuthDomainDigest where
gobjectType :: IO GType
gobjectType = IO GType
c_soup_auth_domain_digest_get_type
instance B.GValue.IsGValue AuthDomainDigest where
toGValue :: AuthDomainDigest -> IO GValue
toGValue o :: AuthDomainDigest
o = do
GType
gtype <- IO GType
c_soup_auth_domain_digest_get_type
AuthDomainDigest
-> (Ptr AuthDomainDigest -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AuthDomainDigest
o (GType
-> (GValue -> Ptr AuthDomainDigest -> IO ())
-> Ptr AuthDomainDigest
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr AuthDomainDigest -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO AuthDomainDigest
fromGValue gv :: GValue
gv = do
Ptr AuthDomainDigest
ptr <- GValue -> IO (Ptr AuthDomainDigest)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr AuthDomainDigest)
(ManagedPtr AuthDomainDigest -> AuthDomainDigest)
-> Ptr AuthDomainDigest -> IO AuthDomainDigest
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr AuthDomainDigest -> AuthDomainDigest
AuthDomainDigest Ptr AuthDomainDigest
ptr
class (GObject o, O.IsDescendantOf AuthDomainDigest o) => IsAuthDomainDigest o
instance (GObject o, O.IsDescendantOf AuthDomainDigest o) => IsAuthDomainDigest o
instance O.HasParentTypes AuthDomainDigest
type instance O.ParentTypes AuthDomainDigest = '[Soup.AuthDomain.AuthDomain, GObject.Object.Object]
toAuthDomainDigest :: (MonadIO m, IsAuthDomainDigest o) => o -> m AuthDomainDigest
toAuthDomainDigest :: o -> m AuthDomainDigest
toAuthDomainDigest = IO AuthDomainDigest -> m AuthDomainDigest
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AuthDomainDigest -> m AuthDomainDigest)
-> (o -> IO AuthDomainDigest) -> o -> m AuthDomainDigest
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr AuthDomainDigest -> AuthDomainDigest)
-> o -> IO AuthDomainDigest
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr AuthDomainDigest -> AuthDomainDigest
AuthDomainDigest
noAuthDomainDigest :: Maybe AuthDomainDigest
noAuthDomainDigest :: Maybe AuthDomainDigest
noAuthDomainDigest = Maybe AuthDomainDigest
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveAuthDomainDigestMethod (t :: Symbol) (o :: *) :: * where
ResolveAuthDomainDigestMethod "accepts" o = Soup.AuthDomain.AuthDomainAcceptsMethodInfo
ResolveAuthDomainDigestMethod "addPath" o = Soup.AuthDomain.AuthDomainAddPathMethodInfo
ResolveAuthDomainDigestMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveAuthDomainDigestMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveAuthDomainDigestMethod "challenge" o = Soup.AuthDomain.AuthDomainChallengeMethodInfo
ResolveAuthDomainDigestMethod "checkPassword" o = Soup.AuthDomain.AuthDomainCheckPasswordMethodInfo
ResolveAuthDomainDigestMethod "covers" o = Soup.AuthDomain.AuthDomainCoversMethodInfo
ResolveAuthDomainDigestMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveAuthDomainDigestMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveAuthDomainDigestMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveAuthDomainDigestMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveAuthDomainDigestMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveAuthDomainDigestMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveAuthDomainDigestMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveAuthDomainDigestMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveAuthDomainDigestMethod "removePath" o = Soup.AuthDomain.AuthDomainRemovePathMethodInfo
ResolveAuthDomainDigestMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveAuthDomainDigestMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveAuthDomainDigestMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveAuthDomainDigestMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveAuthDomainDigestMethod "tryGenericAuthCallback" o = Soup.AuthDomain.AuthDomainTryGenericAuthCallbackMethodInfo
ResolveAuthDomainDigestMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveAuthDomainDigestMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveAuthDomainDigestMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveAuthDomainDigestMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveAuthDomainDigestMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveAuthDomainDigestMethod "getRealm" o = Soup.AuthDomain.AuthDomainGetRealmMethodInfo
ResolveAuthDomainDigestMethod "setAuthCallback" o = AuthDomainDigestSetAuthCallbackMethodInfo
ResolveAuthDomainDigestMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveAuthDomainDigestMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveAuthDomainDigestMethod "setFilter" o = Soup.AuthDomain.AuthDomainSetFilterMethodInfo
ResolveAuthDomainDigestMethod "setGenericAuthCallback" o = Soup.AuthDomain.AuthDomainSetGenericAuthCallbackMethodInfo
ResolveAuthDomainDigestMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveAuthDomainDigestMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveAuthDomainDigestMethod t AuthDomainDigest, O.MethodInfo info AuthDomainDigest p) => OL.IsLabel t (AuthDomainDigest -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
getAuthDomainDigestAuthCallback :: (MonadIO m, IsAuthDomainDigest o) => o -> m (Maybe Soup.Callbacks.AuthDomainDigestAuthCallback_WithClosures)
getAuthDomainDigestAuthCallback :: o -> m (Maybe AuthDomainDigestAuthCallback_WithClosures)
getAuthDomainDigestAuthCallback obj :: o
obj = IO (Maybe AuthDomainDigestAuthCallback_WithClosures)
-> m (Maybe AuthDomainDigestAuthCallback_WithClosures)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe AuthDomainDigestAuthCallback_WithClosures)
-> m (Maybe AuthDomainDigestAuthCallback_WithClosures))
-> IO (Maybe AuthDomainDigestAuthCallback_WithClosures)
-> m (Maybe AuthDomainDigestAuthCallback_WithClosures)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (FunPtr C_AuthDomainDigestAuthCallback
-> AuthDomainDigestAuthCallback_WithClosures)
-> IO (Maybe AuthDomainDigestAuthCallback_WithClosures)
forall a b c.
GObject a =>
a -> String -> (FunPtr b -> c) -> IO (Maybe c)
B.Properties.getObjectPropertyCallback o
obj "auth-callback" FunPtr C_AuthDomainDigestAuthCallback
-> AuthDomainDigestAuthCallback_WithClosures
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsAuthDomainDigest a, IsMessage b) =>
FunPtr C_AuthDomainDigestAuthCallback
-> a -> b -> Text -> Ptr () -> m (Maybe Text)
Soup.Callbacks.dynamic_AuthDomainDigestAuthCallback
setAuthDomainDigestAuthCallback :: (MonadIO m, IsAuthDomainDigest o) => o -> FunPtr Soup.Callbacks.C_AuthDomainDigestAuthCallback -> m ()
setAuthDomainDigestAuthCallback :: o -> FunPtr C_AuthDomainDigestAuthCallback -> m ()
setAuthDomainDigestAuthCallback obj :: o
obj val :: FunPtr C_AuthDomainDigestAuthCallback
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 -> FunPtr C_AuthDomainDigestAuthCallback -> IO ()
forall a b. GObject a => a -> String -> FunPtr b -> IO ()
B.Properties.setObjectPropertyCallback o
obj "auth-callback" FunPtr C_AuthDomainDigestAuthCallback
val
constructAuthDomainDigestAuthCallback :: (IsAuthDomainDigest o) => FunPtr Soup.Callbacks.C_AuthDomainDigestAuthCallback -> IO (GValueConstruct o)
constructAuthDomainDigestAuthCallback :: FunPtr C_AuthDomainDigestAuthCallback -> IO (GValueConstruct o)
constructAuthDomainDigestAuthCallback val :: FunPtr C_AuthDomainDigestAuthCallback
val = String
-> FunPtr C_AuthDomainDigestAuthCallback -> IO (GValueConstruct o)
forall b o. String -> FunPtr b -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyCallback "auth-callback" FunPtr C_AuthDomainDigestAuthCallback
val
clearAuthDomainDigestAuthCallback :: (MonadIO m, IsAuthDomainDigest o) => o -> m ()
clearAuthDomainDigestAuthCallback :: o -> m ()
clearAuthDomainDigestAuthCallback obj :: 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 -> FunPtr Any -> IO ()
forall a b. GObject a => a -> String -> FunPtr b -> IO ()
B.Properties.setObjectPropertyCallback o
obj "auth-callback" FunPtr Any
forall a. FunPtr a
FP.nullFunPtr
#if defined(ENABLE_OVERLOADING)
data AuthDomainDigestAuthCallbackPropertyInfo
instance AttrInfo AuthDomainDigestAuthCallbackPropertyInfo where
type AttrAllowedOps AuthDomainDigestAuthCallbackPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint AuthDomainDigestAuthCallbackPropertyInfo = IsAuthDomainDigest
type AttrSetTypeConstraint AuthDomainDigestAuthCallbackPropertyInfo = (~) (FunPtr Soup.Callbacks.C_AuthDomainDigestAuthCallback)
type AttrTransferTypeConstraint AuthDomainDigestAuthCallbackPropertyInfo = (~) Soup.Callbacks.AuthDomainDigestAuthCallback_WithClosures
type AttrTransferType AuthDomainDigestAuthCallbackPropertyInfo = FunPtr Soup.Callbacks.C_AuthDomainDigestAuthCallback
type AttrGetType AuthDomainDigestAuthCallbackPropertyInfo = (Maybe Soup.Callbacks.AuthDomainDigestAuthCallback_WithClosures)
type AttrLabel AuthDomainDigestAuthCallbackPropertyInfo = "auth-callback"
type AttrOrigin AuthDomainDigestAuthCallbackPropertyInfo = AuthDomainDigest
attrGet = getAuthDomainDigestAuthCallback
attrSet = setAuthDomainDigestAuthCallback
attrTransfer _ v = do
Soup.Callbacks.mk_AuthDomainDigestAuthCallback (Soup.Callbacks.wrap_AuthDomainDigestAuthCallback Nothing v)
attrConstruct = constructAuthDomainDigestAuthCallback
attrClear = clearAuthDomainDigestAuthCallback
#endif
getAuthDomainDigestAuthData :: (MonadIO m, IsAuthDomainDigest o) => o -> m (Ptr ())
getAuthDomainDigestAuthData :: o -> m (Ptr ())
getAuthDomainDigestAuthData obj :: 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 "auth-data"
setAuthDomainDigestAuthData :: (MonadIO m, IsAuthDomainDigest o) => o -> Ptr () -> m ()
setAuthDomainDigestAuthData :: o -> Ptr () -> m ()
setAuthDomainDigestAuthData obj :: o
obj val :: Ptr ()
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 -> Ptr () -> IO ()
forall a b. GObject a => a -> String -> Ptr b -> IO ()
B.Properties.setObjectPropertyPtr o
obj "auth-data" Ptr ()
val
constructAuthDomainDigestAuthData :: (IsAuthDomainDigest o) => Ptr () -> IO (GValueConstruct o)
constructAuthDomainDigestAuthData :: Ptr () -> IO (GValueConstruct o)
constructAuthDomainDigestAuthData val :: Ptr ()
val = String -> Ptr () -> IO (GValueConstruct o)
forall b o. String -> Ptr b -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyPtr "auth-data" Ptr ()
val
#if defined(ENABLE_OVERLOADING)
data AuthDomainDigestAuthDataPropertyInfo
instance AttrInfo AuthDomainDigestAuthDataPropertyInfo where
type AttrAllowedOps AuthDomainDigestAuthDataPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint AuthDomainDigestAuthDataPropertyInfo = IsAuthDomainDigest
type AttrSetTypeConstraint AuthDomainDigestAuthDataPropertyInfo = (~) (Ptr ())
type AttrTransferTypeConstraint AuthDomainDigestAuthDataPropertyInfo = (~) (Ptr ())
type AttrTransferType AuthDomainDigestAuthDataPropertyInfo = Ptr ()
type AttrGetType AuthDomainDigestAuthDataPropertyInfo = (Ptr ())
type AttrLabel AuthDomainDigestAuthDataPropertyInfo = "auth-data"
type AttrOrigin AuthDomainDigestAuthDataPropertyInfo = AuthDomainDigest
attrGet = getAuthDomainDigestAuthData
attrSet = setAuthDomainDigestAuthData
attrTransfer _ v = do
return v
attrConstruct = constructAuthDomainDigestAuthData
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AuthDomainDigest
type instance O.AttributeList AuthDomainDigest = AuthDomainDigestAttributeList
type AuthDomainDigestAttributeList = ('[ '("addPath", Soup.AuthDomain.AuthDomainAddPathPropertyInfo), '("authCallback", AuthDomainDigestAuthCallbackPropertyInfo), '("authData", AuthDomainDigestAuthDataPropertyInfo), '("filter", Soup.AuthDomain.AuthDomainFilterPropertyInfo), '("filterData", Soup.AuthDomain.AuthDomainFilterDataPropertyInfo), '("genericAuthCallback", Soup.AuthDomain.AuthDomainGenericAuthCallbackPropertyInfo), '("genericAuthData", Soup.AuthDomain.AuthDomainGenericAuthDataPropertyInfo), '("proxy", Soup.AuthDomain.AuthDomainProxyPropertyInfo), '("realm", Soup.AuthDomain.AuthDomainRealmPropertyInfo), '("removePath", Soup.AuthDomain.AuthDomainRemovePathPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
authDomainDigestAuthCallback :: AttrLabelProxy "authCallback"
authDomainDigestAuthCallback = AttrLabelProxy
authDomainDigestAuthData :: AttrLabelProxy "authData"
authDomainDigestAuthData = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList AuthDomainDigest = AuthDomainDigestSignalList
type AuthDomainDigestSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "soup_auth_domain_digest_set_auth_callback" soup_auth_domain_digest_set_auth_callback ::
Ptr AuthDomainDigest ->
FunPtr Soup.Callbacks.C_AuthDomainDigestAuthCallback ->
Ptr () ->
FunPtr GLib.Callbacks.C_DestroyNotify ->
IO ()
authDomainDigestSetAuthCallback ::
(B.CallStack.HasCallStack, MonadIO m, IsAuthDomainDigest a) =>
a
-> Soup.Callbacks.AuthDomainDigestAuthCallback
-> m ()
authDomainDigestSetAuthCallback :: a -> AuthDomainDigestAuthCallback -> m ()
authDomainDigestSetAuthCallback domain :: a
domain callback :: AuthDomainDigestAuthCallback
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 AuthDomainDigest
domain' <- a -> IO (Ptr AuthDomainDigest)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
domain
FunPtr C_AuthDomainDigestAuthCallback
callback' <- C_AuthDomainDigestAuthCallback
-> IO (FunPtr C_AuthDomainDigestAuthCallback)
Soup.Callbacks.mk_AuthDomainDigestAuthCallback (Maybe (Ptr (FunPtr C_AuthDomainDigestAuthCallback))
-> AuthDomainDigestAuthCallback_WithClosures
-> C_AuthDomainDigestAuthCallback
Soup.Callbacks.wrap_AuthDomainDigestAuthCallback Maybe (Ptr (FunPtr C_AuthDomainDigestAuthCallback))
forall a. Maybe a
Nothing (AuthDomainDigestAuthCallback
-> AuthDomainDigestAuthCallback_WithClosures
Soup.Callbacks.drop_closures_AuthDomainDigestAuthCallback AuthDomainDigestAuthCallback
callback))
let userData :: Ptr ()
userData = FunPtr C_AuthDomainDigestAuthCallback -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_AuthDomainDigestAuthCallback
callback'
let dnotify :: FunPtr (Ptr a -> IO ())
dnotify = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
safeFreeFunPtrPtr
Ptr AuthDomainDigest
-> FunPtr C_AuthDomainDigestAuthCallback
-> Ptr ()
-> FunPtr (Ptr () -> IO ())
-> IO ()
soup_auth_domain_digest_set_auth_callback Ptr AuthDomainDigest
domain' FunPtr C_AuthDomainDigestAuthCallback
callback' Ptr ()
userData FunPtr (Ptr () -> IO ())
forall a. FunPtr (Ptr a -> IO ())
dnotify
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
domain
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AuthDomainDigestSetAuthCallbackMethodInfo
instance (signature ~ (Soup.Callbacks.AuthDomainDigestAuthCallback -> m ()), MonadIO m, IsAuthDomainDigest a) => O.MethodInfo AuthDomainDigestSetAuthCallbackMethodInfo a signature where
overloadedMethod = authDomainDigestSetAuthCallback
#endif
foreign import ccall "soup_auth_domain_digest_encode_password" soup_auth_domain_digest_encode_password ::
CString ->
CString ->
CString ->
IO CString
authDomainDigestEncodePassword ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> T.Text
-> T.Text
-> m T.Text
authDomainDigestEncodePassword :: Text -> Text -> Text -> m Text
authDomainDigestEncodePassword username :: Text
username realm :: Text
realm password :: Text
password = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
CString
username' <- Text -> IO CString
textToCString Text
username
CString
realm' <- Text -> IO CString
textToCString Text
realm
CString
password' <- Text -> IO CString
textToCString Text
password
CString
result <- CString -> CString -> CString -> IO CString
soup_auth_domain_digest_encode_password CString
username' CString
realm' CString
password'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "authDomainDigestEncodePassword" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
username'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
realm'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
password'
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
#endif