{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Soup.Objects.AuthDomain
    ( 

-- * Exported types
    AuthDomain(..)                          ,
    IsAuthDomain                            ,
    toAuthDomain                            ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [accepts]("GI.Soup.Objects.AuthDomain#g:method:accepts"), [addPath]("GI.Soup.Objects.AuthDomain#g:method:addPath"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [challenge]("GI.Soup.Objects.AuthDomain#g:method:challenge"), [checkPassword]("GI.Soup.Objects.AuthDomain#g:method:checkPassword"), [covers]("GI.Soup.Objects.AuthDomain#g:method:covers"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removePath]("GI.Soup.Objects.AuthDomain#g:method:removePath"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [tryGenericAuthCallback]("GI.Soup.Objects.AuthDomain#g:method:tryGenericAuthCallback"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRealm]("GI.Soup.Objects.AuthDomain#g:method:getRealm").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setFilter]("GI.Soup.Objects.AuthDomain#g:method:setFilter"), [setGenericAuthCallback]("GI.Soup.Objects.AuthDomain#g:method:setGenericAuthCallback"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveAuthDomainMethod                 ,
#endif

-- ** accepts #method:accepts#

#if defined(ENABLE_OVERLOADING)
    AuthDomainAcceptsMethodInfo             ,
#endif
    authDomainAccepts                       ,


-- ** addPath #method:addPath#

#if defined(ENABLE_OVERLOADING)
    AuthDomainAddPathMethodInfo             ,
#endif
    authDomainAddPath                       ,


-- ** challenge #method:challenge#

#if defined(ENABLE_OVERLOADING)
    AuthDomainChallengeMethodInfo           ,
#endif
    authDomainChallenge                     ,


-- ** checkPassword #method:checkPassword#

#if defined(ENABLE_OVERLOADING)
    AuthDomainCheckPasswordMethodInfo       ,
#endif
    authDomainCheckPassword                 ,


-- ** covers #method:covers#

#if defined(ENABLE_OVERLOADING)
    AuthDomainCoversMethodInfo              ,
#endif
    authDomainCovers                        ,


-- ** getRealm #method:getRealm#

#if defined(ENABLE_OVERLOADING)
    AuthDomainGetRealmMethodInfo            ,
#endif
    authDomainGetRealm                      ,


-- ** removePath #method:removePath#

#if defined(ENABLE_OVERLOADING)
    AuthDomainRemovePathMethodInfo          ,
#endif
    authDomainRemovePath                    ,


-- ** setFilter #method:setFilter#

#if defined(ENABLE_OVERLOADING)
    AuthDomainSetFilterMethodInfo           ,
#endif
    authDomainSetFilter                     ,


-- ** setGenericAuthCallback #method:setGenericAuthCallback#

#if defined(ENABLE_OVERLOADING)
    AuthDomainSetGenericAuthCallbackMethodInfo,
#endif
    authDomainSetGenericAuthCallback        ,


-- ** tryGenericAuthCallback #method:tryGenericAuthCallback#

#if defined(ENABLE_OVERLOADING)
    AuthDomainTryGenericAuthCallbackMethodInfo,
#endif
    authDomainTryGenericAuthCallback        ,




 -- * Properties


-- ** addPath #attr:addPath#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    AuthDomainAddPathPropertyInfo           ,
#endif
    clearAuthDomainAddPath                  ,
    constructAuthDomainAddPath              ,
    setAuthDomainAddPath                    ,


-- ** filter #attr:filter#
-- | The t'GI.Soup.Callbacks.AuthDomainFilter' for the domain

#if defined(ENABLE_OVERLOADING)
    AuthDomainFilterPropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    authDomainFilter                        ,
#endif
    clearAuthDomainFilter                   ,
    constructAuthDomainFilter               ,
    getAuthDomainFilter                     ,
    setAuthDomainFilter                     ,


-- ** filterData #attr:filterData#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    AuthDomainFilterDataPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    authDomainFilterData                    ,
#endif
    constructAuthDomainFilterData           ,
    getAuthDomainFilterData                 ,
    setAuthDomainFilterData                 ,


-- ** genericAuthCallback #attr:genericAuthCallback#
-- | The t'GI.Soup.Callbacks.AuthDomainGenericAuthCallback' for the domain

#if defined(ENABLE_OVERLOADING)
    AuthDomainGenericAuthCallbackPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    authDomainGenericAuthCallback           ,
#endif
    clearAuthDomainGenericAuthCallback      ,
    constructAuthDomainGenericAuthCallback  ,
    getAuthDomainGenericAuthCallback        ,
    setAuthDomainGenericAuthCallback        ,


-- ** genericAuthData #attr:genericAuthData#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    AuthDomainGenericAuthDataPropertyInfo   ,
#endif
#if defined(ENABLE_OVERLOADING)
    authDomainGenericAuthData               ,
#endif
    constructAuthDomainGenericAuthData      ,
    getAuthDomainGenericAuthData            ,
    setAuthDomainGenericAuthData            ,


-- ** proxy #attr:proxy#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    AuthDomainProxyPropertyInfo             ,
#endif
#if defined(ENABLE_OVERLOADING)
    authDomainProxy                         ,
#endif
    constructAuthDomainProxy                ,
    getAuthDomainProxy                      ,


-- ** realm #attr:realm#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    AuthDomainRealmPropertyInfo             ,
#endif
#if defined(ENABLE_OVERLOADING)
    authDomainRealm                         ,
#endif
    constructAuthDomainRealm                ,
    getAuthDomainRealm                      ,


-- ** removePath #attr:removePath#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    AuthDomainRemovePathPropertyInfo        ,
#endif
    clearAuthDomainRemovePath               ,
    constructAuthDomainRemovePath           ,
    setAuthDomainRemovePath                 ,




    ) 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.GArray as B.GArray
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.Coerce as Coerce
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 GHC.Records as R

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.Message as Soup.Message

-- | Memory-managed wrapper type.
newtype AuthDomain = AuthDomain (SP.ManagedPtr AuthDomain)
    deriving (AuthDomain -> AuthDomain -> Bool
(AuthDomain -> AuthDomain -> Bool)
-> (AuthDomain -> AuthDomain -> Bool) -> Eq AuthDomain
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthDomain -> AuthDomain -> Bool
$c/= :: AuthDomain -> AuthDomain -> Bool
== :: AuthDomain -> AuthDomain -> Bool
$c== :: AuthDomain -> AuthDomain -> Bool
Eq)

instance SP.ManagedPtrNewtype AuthDomain where
    toManagedPtr :: AuthDomain -> ManagedPtr AuthDomain
toManagedPtr (AuthDomain ManagedPtr AuthDomain
p) = ManagedPtr AuthDomain
p

foreign import ccall "soup_auth_domain_get_type"
    c_soup_auth_domain_get_type :: IO B.Types.GType

instance B.Types.TypedObject AuthDomain where
    glibType :: IO GType
glibType = IO GType
c_soup_auth_domain_get_type

instance B.Types.GObject AuthDomain

-- | Type class for types which can be safely cast to `AuthDomain`, for instance with `toAuthDomain`.
class (SP.GObject o, O.IsDescendantOf AuthDomain o) => IsAuthDomain o
instance (SP.GObject o, O.IsDescendantOf AuthDomain o) => IsAuthDomain o

instance O.HasParentTypes AuthDomain
type instance O.ParentTypes AuthDomain = '[GObject.Object.Object]

-- | Cast to `AuthDomain`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toAuthDomain :: (MIO.MonadIO m, IsAuthDomain o) => o -> m AuthDomain
toAuthDomain :: forall (m :: * -> *) o.
(MonadIO m, IsAuthDomain o) =>
o -> m AuthDomain
toAuthDomain = IO AuthDomain -> m AuthDomain
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO AuthDomain -> m AuthDomain)
-> (o -> IO AuthDomain) -> o -> m AuthDomain
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr AuthDomain -> AuthDomain) -> o -> IO AuthDomain
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr AuthDomain -> AuthDomain
AuthDomain

-- | Convert 'AuthDomain' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe AuthDomain) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_soup_auth_domain_get_type
    gvalueSet_ :: Ptr GValue -> Maybe AuthDomain -> IO ()
gvalueSet_ Ptr GValue
gv Maybe AuthDomain
P.Nothing = Ptr GValue -> Ptr AuthDomain -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr AuthDomain
forall a. Ptr a
FP.nullPtr :: FP.Ptr AuthDomain)
    gvalueSet_ Ptr GValue
gv (P.Just AuthDomain
obj) = AuthDomain -> (Ptr AuthDomain -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AuthDomain
obj (Ptr GValue -> Ptr AuthDomain -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe AuthDomain)
gvalueGet_ Ptr GValue
gv = do
        Ptr AuthDomain
ptr <- Ptr GValue -> IO (Ptr AuthDomain)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr AuthDomain)
        if Ptr AuthDomain
ptr Ptr AuthDomain -> Ptr AuthDomain -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr AuthDomain
forall a. Ptr a
FP.nullPtr
        then AuthDomain -> Maybe AuthDomain
forall a. a -> Maybe a
P.Just (AuthDomain -> Maybe AuthDomain)
-> IO AuthDomain -> IO (Maybe AuthDomain)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr AuthDomain -> AuthDomain)
-> Ptr AuthDomain -> IO AuthDomain
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr AuthDomain -> AuthDomain
AuthDomain Ptr AuthDomain
ptr
        else Maybe AuthDomain -> IO (Maybe AuthDomain)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AuthDomain
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveAuthDomainMethod (t :: Symbol) (o :: *) :: * where
    ResolveAuthDomainMethod "accepts" o = AuthDomainAcceptsMethodInfo
    ResolveAuthDomainMethod "addPath" o = AuthDomainAddPathMethodInfo
    ResolveAuthDomainMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveAuthDomainMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveAuthDomainMethod "challenge" o = AuthDomainChallengeMethodInfo
    ResolveAuthDomainMethod "checkPassword" o = AuthDomainCheckPasswordMethodInfo
    ResolveAuthDomainMethod "covers" o = AuthDomainCoversMethodInfo
    ResolveAuthDomainMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveAuthDomainMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveAuthDomainMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveAuthDomainMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveAuthDomainMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveAuthDomainMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveAuthDomainMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveAuthDomainMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveAuthDomainMethod "removePath" o = AuthDomainRemovePathMethodInfo
    ResolveAuthDomainMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveAuthDomainMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveAuthDomainMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveAuthDomainMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveAuthDomainMethod "tryGenericAuthCallback" o = AuthDomainTryGenericAuthCallbackMethodInfo
    ResolveAuthDomainMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveAuthDomainMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveAuthDomainMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveAuthDomainMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveAuthDomainMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveAuthDomainMethod "getRealm" o = AuthDomainGetRealmMethodInfo
    ResolveAuthDomainMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveAuthDomainMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveAuthDomainMethod "setFilter" o = AuthDomainSetFilterMethodInfo
    ResolveAuthDomainMethod "setGenericAuthCallback" o = AuthDomainSetGenericAuthCallbackMethodInfo
    ResolveAuthDomainMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveAuthDomainMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveAuthDomainMethod t AuthDomain, O.OverloadedMethod info AuthDomain p) => OL.IsLabel t (AuthDomain -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveAuthDomainMethod t AuthDomain, O.OverloadedMethod info AuthDomain p, R.HasField t AuthDomain p) => R.HasField t AuthDomain p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveAuthDomainMethod t AuthDomain, O.OverloadedMethodInfo info AuthDomain) => OL.IsLabel t (O.MethodProxy info AuthDomain) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "add-path"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Set the value of the “@add-path@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' authDomain [ #addPath 'Data.GI.Base.Attributes.:=' value ]
-- @
setAuthDomainAddPath :: (MonadIO m, IsAuthDomain o) => o -> T.Text -> m ()
setAuthDomainAddPath :: forall (m :: * -> *) o.
(MonadIO m, IsAuthDomain o) =>
o -> Text -> m ()
setAuthDomainAddPath o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"add-path" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@add-path@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructAuthDomainAddPath :: (IsAuthDomain o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructAuthDomainAddPath :: forall o (m :: * -> *).
(IsAuthDomain o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructAuthDomainAddPath 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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
"add-path" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@add-path@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #addPath
-- @
clearAuthDomainAddPath :: (MonadIO m, IsAuthDomain o) => o -> m ()
clearAuthDomainAddPath :: forall (m :: * -> *) o. (MonadIO m, IsAuthDomain o) => o -> m ()
clearAuthDomainAddPath 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
"add-path" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data AuthDomainAddPathPropertyInfo
instance AttrInfo AuthDomainAddPathPropertyInfo where
    type AttrAllowedOps AuthDomainAddPathPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrClear]
    type AttrBaseTypeConstraint AuthDomainAddPathPropertyInfo = IsAuthDomain
    type AttrSetTypeConstraint AuthDomainAddPathPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint AuthDomainAddPathPropertyInfo = (~) T.Text
    type AttrTransferType AuthDomainAddPathPropertyInfo = T.Text
    type AttrGetType AuthDomainAddPathPropertyInfo = ()
    type AttrLabel AuthDomainAddPathPropertyInfo = "add-path"
    type AttrOrigin AuthDomainAddPathPropertyInfo = AuthDomain
    attrGet = undefined
    attrSet = setAuthDomainAddPath
    attrTransfer _ v = do
        return v
    attrConstruct = constructAuthDomainAddPath
    attrClear = clearAuthDomainAddPath
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.addPath"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#g:attr:addPath"
        })
#endif

-- VVV Prop "filter"
   -- Type: TInterface (Name {namespace = "Soup", name = "AuthDomainFilter"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@filter@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' authDomain #filter
-- @
getAuthDomainFilter :: (MonadIO m, IsAuthDomain o) => o -> m (Maybe Soup.Callbacks.AuthDomainFilter_WithClosures)
getAuthDomainFilter :: forall (m :: * -> *) o.
(MonadIO m, IsAuthDomain o) =>
o -> m (Maybe AuthDomainFilter_WithClosures)
getAuthDomainFilter o
obj = IO (Maybe AuthDomainFilter_WithClosures)
-> m (Maybe AuthDomainFilter_WithClosures)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe AuthDomainFilter_WithClosures)
 -> m (Maybe AuthDomainFilter_WithClosures))
-> IO (Maybe AuthDomainFilter_WithClosures)
-> m (Maybe AuthDomainFilter_WithClosures)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (FunPtr C_AuthDomainFilter -> AuthDomainFilter_WithClosures)
-> IO (Maybe AuthDomainFilter_WithClosures)
forall a b c.
GObject a =>
a -> String -> (FunPtr b -> c) -> IO (Maybe c)
B.Properties.getObjectPropertyCallback o
obj String
"filter" FunPtr C_AuthDomainFilter -> AuthDomainFilter_WithClosures
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsAuthDomain a, IsMessage b) =>
FunPtr C_AuthDomainFilter -> a -> b -> Ptr () -> m Bool
Soup.Callbacks.dynamic_AuthDomainFilter

-- | Set the value of the “@filter@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' authDomain [ #filter 'Data.GI.Base.Attributes.:=' value ]
-- @
setAuthDomainFilter :: (MonadIO m, IsAuthDomain o) => o -> FunPtr Soup.Callbacks.C_AuthDomainFilter -> m ()
setAuthDomainFilter :: forall (m :: * -> *) o.
(MonadIO m, IsAuthDomain o) =>
o -> FunPtr C_AuthDomainFilter -> m ()
setAuthDomainFilter o
obj FunPtr C_AuthDomainFilter
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> FunPtr C_AuthDomainFilter -> IO ()
forall a b. GObject a => a -> String -> FunPtr b -> IO ()
B.Properties.setObjectPropertyCallback o
obj String
"filter" FunPtr C_AuthDomainFilter
val

-- | Construct a `GValueConstruct` with valid value for the “@filter@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructAuthDomainFilter :: (IsAuthDomain o, MIO.MonadIO m) => FunPtr Soup.Callbacks.C_AuthDomainFilter -> m (GValueConstruct o)
constructAuthDomainFilter :: forall o (m :: * -> *).
(IsAuthDomain o, MonadIO m) =>
FunPtr C_AuthDomainFilter -> m (GValueConstruct o)
constructAuthDomainFilter FunPtr C_AuthDomainFilter
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> FunPtr C_AuthDomainFilter -> IO (GValueConstruct o)
forall b o. String -> FunPtr b -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyCallback String
"filter" FunPtr C_AuthDomainFilter
val

-- | Set the value of the “@filter@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #filter
-- @
clearAuthDomainFilter :: (MonadIO m, IsAuthDomain o) => o -> m ()
clearAuthDomainFilter :: forall (m :: * -> *) o. (MonadIO m, IsAuthDomain o) => o -> m ()
clearAuthDomainFilter 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 String
"filter" FunPtr Any
forall a. FunPtr a
FP.nullFunPtr

#if defined(ENABLE_OVERLOADING)
data AuthDomainFilterPropertyInfo
instance AttrInfo AuthDomainFilterPropertyInfo where
    type AttrAllowedOps AuthDomainFilterPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint AuthDomainFilterPropertyInfo = IsAuthDomain
    type AttrSetTypeConstraint AuthDomainFilterPropertyInfo = (~) (FunPtr Soup.Callbacks.C_AuthDomainFilter)
    type AttrTransferTypeConstraint AuthDomainFilterPropertyInfo = (~) Soup.Callbacks.AuthDomainFilter_WithClosures
    type AttrTransferType AuthDomainFilterPropertyInfo = FunPtr Soup.Callbacks.C_AuthDomainFilter
    type AttrGetType AuthDomainFilterPropertyInfo = (Maybe Soup.Callbacks.AuthDomainFilter_WithClosures)
    type AttrLabel AuthDomainFilterPropertyInfo = "filter"
    type AttrOrigin AuthDomainFilterPropertyInfo = AuthDomain
    attrGet = getAuthDomainFilter
    attrSet = setAuthDomainFilter
    attrTransfer _ v = do
        Soup.Callbacks.mk_AuthDomainFilter (Soup.Callbacks.wrap_AuthDomainFilter Nothing v)
    attrConstruct = constructAuthDomainFilter
    attrClear = clearAuthDomainFilter
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.filter"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#g:attr:filter"
        })
#endif

-- VVV Prop "filter-data"
   -- Type: TBasicType TPtr
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@filter-data@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' authDomain #filterData
-- @
getAuthDomainFilterData :: (MonadIO m, IsAuthDomain o) => o -> m (Ptr ())
getAuthDomainFilterData :: forall (m :: * -> *) o.
(MonadIO m, IsAuthDomain o) =>
o -> m (Ptr ())
getAuthDomainFilterData o
obj = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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
"filter-data"

-- | Set the value of the “@filter-data@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' authDomain [ #filterData 'Data.GI.Base.Attributes.:=' value ]
-- @
setAuthDomainFilterData :: (MonadIO m, IsAuthDomain o) => o -> Ptr () -> m ()
setAuthDomainFilterData :: forall (m :: * -> *) o.
(MonadIO m, IsAuthDomain o) =>
o -> Ptr () -> m ()
setAuthDomainFilterData o
obj Ptr ()
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Ptr () -> IO ()
forall a b. GObject a => a -> String -> Ptr b -> IO ()
B.Properties.setObjectPropertyPtr o
obj String
"filter-data" Ptr ()
val

-- | Construct a `GValueConstruct` with valid value for the “@filter-data@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructAuthDomainFilterData :: (IsAuthDomain o, MIO.MonadIO m) => Ptr () -> m (GValueConstruct o)
constructAuthDomainFilterData :: forall o (m :: * -> *).
(IsAuthDomain o, MonadIO m) =>
Ptr () -> m (GValueConstruct o)
constructAuthDomainFilterData 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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
"filter-data" Ptr ()
val

#if defined(ENABLE_OVERLOADING)
data AuthDomainFilterDataPropertyInfo
instance AttrInfo AuthDomainFilterDataPropertyInfo where
    type AttrAllowedOps AuthDomainFilterDataPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint AuthDomainFilterDataPropertyInfo = IsAuthDomain
    type AttrSetTypeConstraint AuthDomainFilterDataPropertyInfo = (~) (Ptr ())
    type AttrTransferTypeConstraint AuthDomainFilterDataPropertyInfo = (~) (Ptr ())
    type AttrTransferType AuthDomainFilterDataPropertyInfo = Ptr ()
    type AttrGetType AuthDomainFilterDataPropertyInfo = (Ptr ())
    type AttrLabel AuthDomainFilterDataPropertyInfo = "filter-data"
    type AttrOrigin AuthDomainFilterDataPropertyInfo = AuthDomain
    attrGet = getAuthDomainFilterData
    attrSet = setAuthDomainFilterData
    attrTransfer _ v = do
        return v
    attrConstruct = constructAuthDomainFilterData
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.filterData"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#g:attr:filterData"
        })
#endif

-- VVV Prop "generic-auth-callback"
   -- Type: TInterface (Name {namespace = "Soup", name = "AuthDomainGenericAuthCallback"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@generic-auth-callback@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' authDomain #genericAuthCallback
-- @
getAuthDomainGenericAuthCallback :: (MonadIO m, IsAuthDomain o) => o -> m (Maybe Soup.Callbacks.AuthDomainGenericAuthCallback_WithClosures)
getAuthDomainGenericAuthCallback :: forall (m :: * -> *) o.
(MonadIO m, IsAuthDomain o) =>
o -> m (Maybe AuthDomainGenericAuthCallback_WithClosures)
getAuthDomainGenericAuthCallback o
obj = IO (Maybe AuthDomainGenericAuthCallback_WithClosures)
-> m (Maybe AuthDomainGenericAuthCallback_WithClosures)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe AuthDomainGenericAuthCallback_WithClosures)
 -> m (Maybe AuthDomainGenericAuthCallback_WithClosures))
-> IO (Maybe AuthDomainGenericAuthCallback_WithClosures)
-> m (Maybe AuthDomainGenericAuthCallback_WithClosures)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (FunPtr C_AuthDomainGenericAuthCallback
    -> AuthDomainGenericAuthCallback_WithClosures)
-> IO (Maybe AuthDomainGenericAuthCallback_WithClosures)
forall a b c.
GObject a =>
a -> String -> (FunPtr b -> c) -> IO (Maybe c)
B.Properties.getObjectPropertyCallback o
obj String
"generic-auth-callback" FunPtr C_AuthDomainGenericAuthCallback
-> AuthDomainGenericAuthCallback_WithClosures
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsAuthDomain a, IsMessage b) =>
FunPtr C_AuthDomainGenericAuthCallback
-> a -> b -> Text -> Ptr () -> m Bool
Soup.Callbacks.dynamic_AuthDomainGenericAuthCallback

-- | Set the value of the “@generic-auth-callback@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' authDomain [ #genericAuthCallback 'Data.GI.Base.Attributes.:=' value ]
-- @
setAuthDomainGenericAuthCallback :: (MonadIO m, IsAuthDomain o) => o -> FunPtr Soup.Callbacks.C_AuthDomainGenericAuthCallback -> m ()
setAuthDomainGenericAuthCallback :: forall (m :: * -> *) o.
(MonadIO m, IsAuthDomain o) =>
o -> FunPtr C_AuthDomainGenericAuthCallback -> m ()
setAuthDomainGenericAuthCallback o
obj FunPtr C_AuthDomainGenericAuthCallback
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> FunPtr C_AuthDomainGenericAuthCallback -> IO ()
forall a b. GObject a => a -> String -> FunPtr b -> IO ()
B.Properties.setObjectPropertyCallback o
obj String
"generic-auth-callback" FunPtr C_AuthDomainGenericAuthCallback
val

-- | Construct a `GValueConstruct` with valid value for the “@generic-auth-callback@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructAuthDomainGenericAuthCallback :: (IsAuthDomain o, MIO.MonadIO m) => FunPtr Soup.Callbacks.C_AuthDomainGenericAuthCallback -> m (GValueConstruct o)
constructAuthDomainGenericAuthCallback :: forall o (m :: * -> *).
(IsAuthDomain o, MonadIO m) =>
FunPtr C_AuthDomainGenericAuthCallback -> m (GValueConstruct o)
constructAuthDomainGenericAuthCallback FunPtr C_AuthDomainGenericAuthCallback
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String
-> FunPtr C_AuthDomainGenericAuthCallback -> IO (GValueConstruct o)
forall b o. String -> FunPtr b -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyCallback String
"generic-auth-callback" FunPtr C_AuthDomainGenericAuthCallback
val

-- | Set the value of the “@generic-auth-callback@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #genericAuthCallback
-- @
clearAuthDomainGenericAuthCallback :: (MonadIO m, IsAuthDomain o) => o -> m ()
clearAuthDomainGenericAuthCallback :: forall (m :: * -> *) o. (MonadIO m, IsAuthDomain o) => o -> m ()
clearAuthDomainGenericAuthCallback 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 String
"generic-auth-callback" FunPtr Any
forall a. FunPtr a
FP.nullFunPtr

#if defined(ENABLE_OVERLOADING)
data AuthDomainGenericAuthCallbackPropertyInfo
instance AttrInfo AuthDomainGenericAuthCallbackPropertyInfo where
    type AttrAllowedOps AuthDomainGenericAuthCallbackPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint AuthDomainGenericAuthCallbackPropertyInfo = IsAuthDomain
    type AttrSetTypeConstraint AuthDomainGenericAuthCallbackPropertyInfo = (~) (FunPtr Soup.Callbacks.C_AuthDomainGenericAuthCallback)
    type AttrTransferTypeConstraint AuthDomainGenericAuthCallbackPropertyInfo = (~) Soup.Callbacks.AuthDomainGenericAuthCallback_WithClosures
    type AttrTransferType AuthDomainGenericAuthCallbackPropertyInfo = FunPtr Soup.Callbacks.C_AuthDomainGenericAuthCallback
    type AttrGetType AuthDomainGenericAuthCallbackPropertyInfo = (Maybe Soup.Callbacks.AuthDomainGenericAuthCallback_WithClosures)
    type AttrLabel AuthDomainGenericAuthCallbackPropertyInfo = "generic-auth-callback"
    type AttrOrigin AuthDomainGenericAuthCallbackPropertyInfo = AuthDomain
    attrGet = getAuthDomainGenericAuthCallback
    attrSet = setAuthDomainGenericAuthCallback
    attrTransfer _ v = do
        Soup.Callbacks.mk_AuthDomainGenericAuthCallback (Soup.Callbacks.wrap_AuthDomainGenericAuthCallback Nothing v)
    attrConstruct = constructAuthDomainGenericAuthCallback
    attrClear = clearAuthDomainGenericAuthCallback
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.genericAuthCallback"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#g:attr:genericAuthCallback"
        })
#endif

-- VVV Prop "generic-auth-data"
   -- Type: TBasicType TPtr
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@generic-auth-data@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' authDomain #genericAuthData
-- @
getAuthDomainGenericAuthData :: (MonadIO m, IsAuthDomain o) => o -> m (Ptr ())
getAuthDomainGenericAuthData :: forall (m :: * -> *) o.
(MonadIO m, IsAuthDomain o) =>
o -> m (Ptr ())
getAuthDomainGenericAuthData o
obj = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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
"generic-auth-data"

-- | Set the value of the “@generic-auth-data@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' authDomain [ #genericAuthData 'Data.GI.Base.Attributes.:=' value ]
-- @
setAuthDomainGenericAuthData :: (MonadIO m, IsAuthDomain o) => o -> Ptr () -> m ()
setAuthDomainGenericAuthData :: forall (m :: * -> *) o.
(MonadIO m, IsAuthDomain o) =>
o -> Ptr () -> m ()
setAuthDomainGenericAuthData o
obj Ptr ()
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Ptr () -> IO ()
forall a b. GObject a => a -> String -> Ptr b -> IO ()
B.Properties.setObjectPropertyPtr o
obj String
"generic-auth-data" Ptr ()
val

-- | Construct a `GValueConstruct` with valid value for the “@generic-auth-data@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructAuthDomainGenericAuthData :: (IsAuthDomain o, MIO.MonadIO m) => Ptr () -> m (GValueConstruct o)
constructAuthDomainGenericAuthData :: forall o (m :: * -> *).
(IsAuthDomain o, MonadIO m) =>
Ptr () -> m (GValueConstruct o)
constructAuthDomainGenericAuthData 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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
"generic-auth-data" Ptr ()
val

#if defined(ENABLE_OVERLOADING)
data AuthDomainGenericAuthDataPropertyInfo
instance AttrInfo AuthDomainGenericAuthDataPropertyInfo where
    type AttrAllowedOps AuthDomainGenericAuthDataPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint AuthDomainGenericAuthDataPropertyInfo = IsAuthDomain
    type AttrSetTypeConstraint AuthDomainGenericAuthDataPropertyInfo = (~) (Ptr ())
    type AttrTransferTypeConstraint AuthDomainGenericAuthDataPropertyInfo = (~) (Ptr ())
    type AttrTransferType AuthDomainGenericAuthDataPropertyInfo = Ptr ()
    type AttrGetType AuthDomainGenericAuthDataPropertyInfo = (Ptr ())
    type AttrLabel AuthDomainGenericAuthDataPropertyInfo = "generic-auth-data"
    type AttrOrigin AuthDomainGenericAuthDataPropertyInfo = AuthDomain
    attrGet = getAuthDomainGenericAuthData
    attrSet = setAuthDomainGenericAuthData
    attrTransfer _ v = do
        return v
    attrConstruct = constructAuthDomainGenericAuthData
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.genericAuthData"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#g:attr:genericAuthData"
        })
#endif

-- VVV Prop "proxy"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@proxy@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' authDomain #proxy
-- @
getAuthDomainProxy :: (MonadIO m, IsAuthDomain o) => o -> m Bool
getAuthDomainProxy :: forall (m :: * -> *) o. (MonadIO m, IsAuthDomain o) => o -> m Bool
getAuthDomainProxy o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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
"proxy"

-- | Construct a `GValueConstruct` with valid value for the “@proxy@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructAuthDomainProxy :: (IsAuthDomain o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructAuthDomainProxy :: forall o (m :: * -> *).
(IsAuthDomain o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructAuthDomainProxy 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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
"proxy" Bool
val

#if defined(ENABLE_OVERLOADING)
data AuthDomainProxyPropertyInfo
instance AttrInfo AuthDomainProxyPropertyInfo where
    type AttrAllowedOps AuthDomainProxyPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint AuthDomainProxyPropertyInfo = IsAuthDomain
    type AttrSetTypeConstraint AuthDomainProxyPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint AuthDomainProxyPropertyInfo = (~) Bool
    type AttrTransferType AuthDomainProxyPropertyInfo = Bool
    type AttrGetType AuthDomainProxyPropertyInfo = Bool
    type AttrLabel AuthDomainProxyPropertyInfo = "proxy"
    type AttrOrigin AuthDomainProxyPropertyInfo = AuthDomain
    attrGet = getAuthDomainProxy
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructAuthDomainProxy
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.proxy"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#g:attr:proxy"
        })
#endif

-- VVV Prop "realm"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@realm@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' authDomain #realm
-- @
getAuthDomainRealm :: (MonadIO m, IsAuthDomain o) => o -> m T.Text
getAuthDomainRealm :: forall (m :: * -> *) o. (MonadIO m, IsAuthDomain o) => o -> m Text
getAuthDomainRealm o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getAuthDomainRealm" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO 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
"realm"

-- | Construct a `GValueConstruct` with valid value for the “@realm@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructAuthDomainRealm :: (IsAuthDomain o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructAuthDomainRealm :: forall o (m :: * -> *).
(IsAuthDomain o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructAuthDomainRealm 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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
"realm" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data AuthDomainRealmPropertyInfo
instance AttrInfo AuthDomainRealmPropertyInfo where
    type AttrAllowedOps AuthDomainRealmPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint AuthDomainRealmPropertyInfo = IsAuthDomain
    type AttrSetTypeConstraint AuthDomainRealmPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint AuthDomainRealmPropertyInfo = (~) T.Text
    type AttrTransferType AuthDomainRealmPropertyInfo = T.Text
    type AttrGetType AuthDomainRealmPropertyInfo = T.Text
    type AttrLabel AuthDomainRealmPropertyInfo = "realm"
    type AttrOrigin AuthDomainRealmPropertyInfo = AuthDomain
    attrGet = getAuthDomainRealm
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructAuthDomainRealm
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.realm"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#g:attr:realm"
        })
#endif

-- VVV Prop "remove-path"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Set the value of the “@remove-path@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' authDomain [ #removePath 'Data.GI.Base.Attributes.:=' value ]
-- @
setAuthDomainRemovePath :: (MonadIO m, IsAuthDomain o) => o -> T.Text -> m ()
setAuthDomainRemovePath :: forall (m :: * -> *) o.
(MonadIO m, IsAuthDomain o) =>
o -> Text -> m ()
setAuthDomainRemovePath o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"remove-path" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@remove-path@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructAuthDomainRemovePath :: (IsAuthDomain o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructAuthDomainRemovePath :: forall o (m :: * -> *).
(IsAuthDomain o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructAuthDomainRemovePath 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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
"remove-path" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@remove-path@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #removePath
-- @
clearAuthDomainRemovePath :: (MonadIO m, IsAuthDomain o) => o -> m ()
clearAuthDomainRemovePath :: forall (m :: * -> *) o. (MonadIO m, IsAuthDomain o) => o -> m ()
clearAuthDomainRemovePath 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
"remove-path" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data AuthDomainRemovePathPropertyInfo
instance AttrInfo AuthDomainRemovePathPropertyInfo where
    type AttrAllowedOps AuthDomainRemovePathPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrClear]
    type AttrBaseTypeConstraint AuthDomainRemovePathPropertyInfo = IsAuthDomain
    type AttrSetTypeConstraint AuthDomainRemovePathPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint AuthDomainRemovePathPropertyInfo = (~) T.Text
    type AttrTransferType AuthDomainRemovePathPropertyInfo = T.Text
    type AttrGetType AuthDomainRemovePathPropertyInfo = ()
    type AttrLabel AuthDomainRemovePathPropertyInfo = "remove-path"
    type AttrOrigin AuthDomainRemovePathPropertyInfo = AuthDomain
    attrGet = undefined
    attrSet = setAuthDomainRemovePath
    attrTransfer _ v = do
        return v
    attrConstruct = constructAuthDomainRemovePath
    attrClear = clearAuthDomainRemovePath
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.removePath"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#g:attr:removePath"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AuthDomain
type instance O.AttributeList AuthDomain = AuthDomainAttributeList
type AuthDomainAttributeList = ('[ '("addPath", AuthDomainAddPathPropertyInfo), '("filter", AuthDomainFilterPropertyInfo), '("filterData", AuthDomainFilterDataPropertyInfo), '("genericAuthCallback", AuthDomainGenericAuthCallbackPropertyInfo), '("genericAuthData", AuthDomainGenericAuthDataPropertyInfo), '("proxy", AuthDomainProxyPropertyInfo), '("realm", AuthDomainRealmPropertyInfo), '("removePath", AuthDomainRemovePathPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
authDomainFilter :: AttrLabelProxy "filter"
authDomainFilter = AttrLabelProxy

authDomainFilterData :: AttrLabelProxy "filterData"
authDomainFilterData = AttrLabelProxy

authDomainGenericAuthCallback :: AttrLabelProxy "genericAuthCallback"
authDomainGenericAuthCallback = AttrLabelProxy

authDomainGenericAuthData :: AttrLabelProxy "genericAuthData"
authDomainGenericAuthData = AttrLabelProxy

authDomainProxy :: AttrLabelProxy "proxy"
authDomainProxy = AttrLabelProxy

authDomainRealm :: AttrLabelProxy "realm"
authDomainRealm = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList AuthDomain = AuthDomainSignalList
type AuthDomainSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method AuthDomain::accepts
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "domain"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "AuthDomain" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #SoupAuthDomain" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "msg"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "Message" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #SoupMessage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "soup_auth_domain_accepts" soup_auth_domain_accepts :: 
    Ptr AuthDomain ->                       -- domain : TInterface (Name {namespace = "Soup", name = "AuthDomain"})
    Ptr Soup.Message.Message ->             -- msg : TInterface (Name {namespace = "Soup", name = "Message"})
    IO CString

-- | Checks if /@msg@/ contains appropriate authorization for /@domain@/ to
-- accept it. Mirroring 'GI.Soup.Objects.AuthDomain.authDomainCovers', this does not check
-- whether or not /@domain@/ \<emphasis>cares\<\/emphasis> if /@msg@/ is
-- authorized.
-- 
-- This is used by t'GI.Soup.Objects.Server.Server' internally and is probably of no use to
-- anyone else.
authDomainAccepts ::
    (B.CallStack.HasCallStack, MonadIO m, IsAuthDomain a, Soup.Message.IsMessage b) =>
    a
    -- ^ /@domain@/: a t'GI.Soup.Objects.AuthDomain.AuthDomain'
    -> b
    -- ^ /@msg@/: a t'GI.Soup.Objects.Message.Message'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the username that /@msg@/ has authenticated
    -- as, if in fact it has authenticated. 'P.Nothing' otherwise.
authDomainAccepts :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsAuthDomain a, IsMessage b) =>
a -> b -> m (Maybe Text)
authDomainAccepts a
domain b
msg = 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
$ do
    Ptr AuthDomain
domain' <- a -> IO (Ptr AuthDomain)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
domain
    Ptr Message
msg' <- b -> IO (Ptr Message)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
msg
    CString
result <- Ptr AuthDomain -> Ptr Message -> IO CString
soup_auth_domain_accepts Ptr AuthDomain
domain' Ptr Message
msg'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
domain
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
msg
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data AuthDomainAcceptsMethodInfo
instance (signature ~ (b -> m (Maybe T.Text)), MonadIO m, IsAuthDomain a, Soup.Message.IsMessage b) => O.OverloadedMethod AuthDomainAcceptsMethodInfo a signature where
    overloadedMethod = authDomainAccepts

instance O.OverloadedMethodInfo AuthDomainAcceptsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.authDomainAccepts",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#v:authDomainAccepts"
        })


#endif

-- method AuthDomain::add_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "domain"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "AuthDomain" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #SoupAuthDomain" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the path to add to @domain"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "soup_auth_domain_add_path" soup_auth_domain_add_path :: 
    Ptr AuthDomain ->                       -- domain : TInterface (Name {namespace = "Soup", name = "AuthDomain"})
    CString ->                              -- path : TBasicType TUTF8
    IO ()

-- | Adds /@path@/ to /@domain@/, such that requests under /@path@/ on /@domain@/\'s
-- server will require authentication (unless overridden by
-- 'GI.Soup.Objects.AuthDomain.authDomainRemovePath' or 'GI.Soup.Objects.AuthDomain.authDomainSetFilter').
-- 
-- You can also add paths by setting the 'GI.Soup.Constants.AUTH_DOMAIN_ADD_PATH'
-- property, which can also be used to add one or more paths at
-- construct time.
authDomainAddPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsAuthDomain a) =>
    a
    -- ^ /@domain@/: a t'GI.Soup.Objects.AuthDomain.AuthDomain'
    -> T.Text
    -- ^ /@path@/: the path to add to /@domain@/
    -> m ()
authDomainAddPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAuthDomain a) =>
a -> Text -> m ()
authDomainAddPath a
domain 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 AuthDomain
domain' <- a -> IO (Ptr AuthDomain)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
domain
    CString
path' <- Text -> IO CString
textToCString Text
path
    Ptr AuthDomain -> CString -> IO ()
soup_auth_domain_add_path Ptr AuthDomain
domain' CString
path'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
domain
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AuthDomainAddPathMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsAuthDomain a) => O.OverloadedMethod AuthDomainAddPathMethodInfo a signature where
    overloadedMethod = authDomainAddPath

instance O.OverloadedMethodInfo AuthDomainAddPathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.authDomainAddPath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#v:authDomainAddPath"
        })


#endif

-- method AuthDomain::challenge
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "domain"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "AuthDomain" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #SoupAuthDomain" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "msg"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "Message" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #SoupMessage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "soup_auth_domain_challenge" soup_auth_domain_challenge :: 
    Ptr AuthDomain ->                       -- domain : TInterface (Name {namespace = "Soup", name = "AuthDomain"})
    Ptr Soup.Message.Message ->             -- msg : TInterface (Name {namespace = "Soup", name = "Message"})
    IO ()

-- | Adds a \"WWW-Authenticate\" or \"Proxy-Authenticate\" header to /@msg@/,
-- requesting that the client authenticate, and sets /@msg@/\'s status
-- accordingly.
-- 
-- This is used by t'GI.Soup.Objects.Server.Server' internally and is probably of no use to
-- anyone else.
authDomainChallenge ::
    (B.CallStack.HasCallStack, MonadIO m, IsAuthDomain a, Soup.Message.IsMessage b) =>
    a
    -- ^ /@domain@/: a t'GI.Soup.Objects.AuthDomain.AuthDomain'
    -> b
    -- ^ /@msg@/: a t'GI.Soup.Objects.Message.Message'
    -> m ()
authDomainChallenge :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsAuthDomain a, IsMessage b) =>
a -> b -> m ()
authDomainChallenge a
domain 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 AuthDomain
domain' <- a -> IO (Ptr AuthDomain)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
domain
    Ptr Message
msg' <- b -> IO (Ptr Message)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
msg
    Ptr AuthDomain -> Ptr Message -> IO ()
soup_auth_domain_challenge Ptr AuthDomain
domain' Ptr Message
msg'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
domain
    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 AuthDomainChallengeMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsAuthDomain a, Soup.Message.IsMessage b) => O.OverloadedMethod AuthDomainChallengeMethodInfo a signature where
    overloadedMethod = authDomainChallenge

instance O.OverloadedMethodInfo AuthDomainChallengeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.authDomainChallenge",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#v:authDomainChallenge"
        })


#endif

-- method AuthDomain::check_password
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "domain"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "AuthDomain" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #SoupAuthDomain" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "msg"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "Message" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #SoupMessage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "username"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a username" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "password"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a password" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "soup_auth_domain_check_password" soup_auth_domain_check_password :: 
    Ptr AuthDomain ->                       -- domain : TInterface (Name {namespace = "Soup", name = "AuthDomain"})
    Ptr Soup.Message.Message ->             -- msg : TInterface (Name {namespace = "Soup", name = "Message"})
    CString ->                              -- username : TBasicType TUTF8
    CString ->                              -- password : TBasicType TUTF8
    IO CInt

-- | Checks if /@msg@/ authenticates to /@domain@/ via /@username@/ and
-- /@password@/. This would normally be called from a
-- t'GI.Soup.Callbacks.AuthDomainGenericAuthCallback'.
authDomainCheckPassword ::
    (B.CallStack.HasCallStack, MonadIO m, IsAuthDomain a, Soup.Message.IsMessage b) =>
    a
    -- ^ /@domain@/: a t'GI.Soup.Objects.AuthDomain.AuthDomain'
    -> b
    -- ^ /@msg@/: a t'GI.Soup.Objects.Message.Message'
    -> T.Text
    -- ^ /@username@/: a username
    -> T.Text
    -- ^ /@password@/: a password
    -> m Bool
    -- ^ __Returns:__ whether or not the message is authenticated
authDomainCheckPassword :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsAuthDomain a, IsMessage b) =>
a -> b -> Text -> Text -> m Bool
authDomainCheckPassword a
domain b
msg Text
username Text
password = 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 AuthDomain
domain' <- a -> IO (Ptr AuthDomain)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
domain
    Ptr Message
msg' <- b -> IO (Ptr Message)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
msg
    CString
username' <- Text -> IO CString
textToCString Text
username
    CString
password' <- Text -> IO CString
textToCString Text
password
    CInt
result <- Ptr AuthDomain -> Ptr Message -> CString -> CString -> IO CInt
soup_auth_domain_check_password Ptr AuthDomain
domain' Ptr Message
msg' CString
username' CString
password'
    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
domain
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
msg
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
username'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
password'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data AuthDomainCheckPasswordMethodInfo
instance (signature ~ (b -> T.Text -> T.Text -> m Bool), MonadIO m, IsAuthDomain a, Soup.Message.IsMessage b) => O.OverloadedMethod AuthDomainCheckPasswordMethodInfo a signature where
    overloadedMethod = authDomainCheckPassword

instance O.OverloadedMethodInfo AuthDomainCheckPasswordMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.authDomainCheckPassword",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#v:authDomainCheckPassword"
        })


#endif

-- method AuthDomain::covers
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "domain"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "AuthDomain" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #SoupAuthDomain" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "msg"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "Message" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #SoupMessage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "soup_auth_domain_covers" soup_auth_domain_covers :: 
    Ptr AuthDomain ->                       -- domain : TInterface (Name {namespace = "Soup", name = "AuthDomain"})
    Ptr Soup.Message.Message ->             -- msg : TInterface (Name {namespace = "Soup", name = "Message"})
    IO CInt

-- | Checks if /@domain@/ requires /@msg@/ to be authenticated (according to
-- its paths and filter function). This does not actually look at
-- whether /@msg@/ \<emphasis>is\<\/emphasis> authenticated, merely whether
-- or not it needs to be.
-- 
-- This is used by t'GI.Soup.Objects.Server.Server' internally and is probably of no use to
-- anyone else.
authDomainCovers ::
    (B.CallStack.HasCallStack, MonadIO m, IsAuthDomain a, Soup.Message.IsMessage b) =>
    a
    -- ^ /@domain@/: a t'GI.Soup.Objects.AuthDomain.AuthDomain'
    -> b
    -- ^ /@msg@/: a t'GI.Soup.Objects.Message.Message'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@domain@/ requires /@msg@/ to be authenticated
authDomainCovers :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsAuthDomain a, IsMessage b) =>
a -> b -> m Bool
authDomainCovers a
domain b
msg = 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 AuthDomain
domain' <- a -> IO (Ptr AuthDomain)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
domain
    Ptr Message
msg' <- b -> IO (Ptr Message)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
msg
    CInt
result <- Ptr AuthDomain -> Ptr Message -> IO CInt
soup_auth_domain_covers Ptr AuthDomain
domain' Ptr Message
msg'
    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
domain
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
msg
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data AuthDomainCoversMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsAuthDomain a, Soup.Message.IsMessage b) => O.OverloadedMethod AuthDomainCoversMethodInfo a signature where
    overloadedMethod = authDomainCovers

instance O.OverloadedMethodInfo AuthDomainCoversMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.authDomainCovers",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#v:authDomainCovers"
        })


#endif

-- method AuthDomain::get_realm
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "domain"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "AuthDomain" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #SoupAuthDomain" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "soup_auth_domain_get_realm" soup_auth_domain_get_realm :: 
    Ptr AuthDomain ->                       -- domain : TInterface (Name {namespace = "Soup", name = "AuthDomain"})
    IO CString

-- | Gets the realm name associated with /@domain@/
authDomainGetRealm ::
    (B.CallStack.HasCallStack, MonadIO m, IsAuthDomain a) =>
    a
    -- ^ /@domain@/: a t'GI.Soup.Objects.AuthDomain.AuthDomain'
    -> m T.Text
    -- ^ __Returns:__ /@domain@/\'s realm
authDomainGetRealm :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAuthDomain a) =>
a -> m Text
authDomainGetRealm a
domain = 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
    Ptr AuthDomain
domain' <- a -> IO (Ptr AuthDomain)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
domain
    CString
result <- Ptr AuthDomain -> IO CString
soup_auth_domain_get_realm Ptr AuthDomain
domain'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"authDomainGetRealm" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
domain
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data AuthDomainGetRealmMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsAuthDomain a) => O.OverloadedMethod AuthDomainGetRealmMethodInfo a signature where
    overloadedMethod = authDomainGetRealm

instance O.OverloadedMethodInfo AuthDomainGetRealmMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.authDomainGetRealm",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#v:authDomainGetRealm"
        })


#endif

-- method AuthDomain::remove_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "domain"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "AuthDomain" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #SoupAuthDomain" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the path to remove from @domain"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "soup_auth_domain_remove_path" soup_auth_domain_remove_path :: 
    Ptr AuthDomain ->                       -- domain : TInterface (Name {namespace = "Soup", name = "AuthDomain"})
    CString ->                              -- path : TBasicType TUTF8
    IO ()

-- | Removes /@path@/ from /@domain@/, such that requests under /@path@/ on
-- /@domain@/\'s server will NOT require authentication.
-- 
-- This is not simply an undo-er for 'GI.Soup.Objects.AuthDomain.authDomainAddPath'; it
-- can be used to \"carve out\" a subtree that does not require
-- authentication inside a hierarchy that does. Note also that unlike
-- with 'GI.Soup.Objects.AuthDomain.authDomainAddPath', this cannot be overridden by
-- adding a filter, as filters can only bypass authentication that
-- would otherwise be required, not require it where it would
-- otherwise be unnecessary.
-- 
-- You can also remove paths by setting the
-- 'GI.Soup.Constants.AUTH_DOMAIN_REMOVE_PATH' property, which can also be used to
-- remove one or more paths at construct time.
authDomainRemovePath ::
    (B.CallStack.HasCallStack, MonadIO m, IsAuthDomain a) =>
    a
    -- ^ /@domain@/: a t'GI.Soup.Objects.AuthDomain.AuthDomain'
    -> T.Text
    -- ^ /@path@/: the path to remove from /@domain@/
    -> m ()
authDomainRemovePath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAuthDomain a) =>
a -> Text -> m ()
authDomainRemovePath a
domain 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 AuthDomain
domain' <- a -> IO (Ptr AuthDomain)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
domain
    CString
path' <- Text -> IO CString
textToCString Text
path
    Ptr AuthDomain -> CString -> IO ()
soup_auth_domain_remove_path Ptr AuthDomain
domain' CString
path'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
domain
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AuthDomainRemovePathMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsAuthDomain a) => O.OverloadedMethod AuthDomainRemovePathMethodInfo a signature where
    overloadedMethod = authDomainRemovePath

instance O.OverloadedMethodInfo AuthDomainRemovePathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.authDomainRemovePath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#v:authDomainRemovePath"
        })


#endif

-- method AuthDomain::set_filter
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "domain"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "AuthDomain" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #SoupAuthDomain" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "filter"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "AuthDomainFilter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the auth filter for @domain"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 2
--           , argDestroy = 3
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "filter_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "data to pass to @filter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dnotify"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "destroy notifier to free @filter_data when @domain\nis destroyed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "soup_auth_domain_set_filter" soup_auth_domain_set_filter :: 
    Ptr AuthDomain ->                       -- domain : TInterface (Name {namespace = "Soup", name = "AuthDomain"})
    FunPtr Soup.Callbacks.C_AuthDomainFilter -> -- filter : TInterface (Name {namespace = "Soup", name = "AuthDomainFilter"})
    Ptr () ->                               -- filter_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- dnotify : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO ()

-- | Adds /@filter@/ as an authentication filter to /@domain@/. The filter
-- gets a chance to bypass authentication for certain requests that
-- would otherwise require it. Eg, it might check the message\'s path
-- in some way that is too complicated to do via the other methods, or
-- it might check the message\'s method, and allow GETs but not PUTs.
-- 
-- The filter function returns 'P.True' if the request should still
-- require authentication, or 'P.False' if authentication is unnecessary
-- for this request.
-- 
-- To help prevent security holes, your filter should return 'P.True' by
-- default, and only return 'P.False' under specifically-tested
-- circumstances, rather than the other way around. Eg, in the example
-- above, where you want to authenticate PUTs but not GETs, you should
-- check if the method is GET and return 'P.False' in that case, and then
-- return 'P.True' for all other methods (rather than returning 'P.True' for
-- PUT and 'P.False' for all other methods). This way if it turned out
-- (now or later) that some paths supported additional methods besides
-- GET and PUT, those methods would default to being NOT allowed for
-- unauthenticated users.
-- 
-- You can also set the filter by setting the 'GI.Soup.Constants.AUTH_DOMAIN_FILTER'
-- and 'GI.Soup.Constants.AUTH_DOMAIN_FILTER_DATA' properties, which can also be
-- used to set the filter at construct time.
authDomainSetFilter ::
    (B.CallStack.HasCallStack, MonadIO m, IsAuthDomain a) =>
    a
    -- ^ /@domain@/: a t'GI.Soup.Objects.AuthDomain.AuthDomain'
    -> Soup.Callbacks.AuthDomainFilter
    -- ^ /@filter@/: the auth filter for /@domain@/
    -> m ()
authDomainSetFilter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAuthDomain a) =>
a -> AuthDomainFilter -> m ()
authDomainSetFilter a
domain AuthDomainFilter
filter = 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 AuthDomain
domain' <- a -> IO (Ptr AuthDomain)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
domain
    FunPtr C_AuthDomainFilter
filter' <- C_AuthDomainFilter -> IO (FunPtr C_AuthDomainFilter)
Soup.Callbacks.mk_AuthDomainFilter (Maybe (Ptr (FunPtr C_AuthDomainFilter))
-> AuthDomainFilter_WithClosures -> C_AuthDomainFilter
Soup.Callbacks.wrap_AuthDomainFilter Maybe (Ptr (FunPtr C_AuthDomainFilter))
forall a. Maybe a
Nothing (AuthDomainFilter -> AuthDomainFilter_WithClosures
Soup.Callbacks.drop_closures_AuthDomainFilter AuthDomainFilter
filter))
    let filterData :: Ptr ()
filterData = FunPtr C_AuthDomainFilter -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_AuthDomainFilter
filter'
    let dnotify :: FunPtr (Ptr a -> IO ())
dnotify = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    Ptr AuthDomain
-> FunPtr C_AuthDomainFilter
-> Ptr ()
-> FunPtr (Ptr () -> IO ())
-> IO ()
soup_auth_domain_set_filter Ptr AuthDomain
domain' FunPtr C_AuthDomainFilter
filter' Ptr ()
filterData 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 AuthDomainSetFilterMethodInfo
instance (signature ~ (Soup.Callbacks.AuthDomainFilter -> m ()), MonadIO m, IsAuthDomain a) => O.OverloadedMethod AuthDomainSetFilterMethodInfo a signature where
    overloadedMethod = authDomainSetFilter

instance O.OverloadedMethodInfo AuthDomainSetFilterMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.authDomainSetFilter",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#v:authDomainSetFilter"
        })


#endif

-- method AuthDomain::set_generic_auth_callback
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "domain"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "AuthDomain" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #SoupAuthDomain" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "auth_callback"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "Soup" , name = "AuthDomainGenericAuthCallback" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the auth callback" , sinceVersion = Nothing }
--           , argScope = ScopeTypeNotified
--           , argClosure = 2
--           , argDestroy = 3
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "auth_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "data to pass to @auth_callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dnotify"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "destroy notifier to free @auth_data when @domain\nis destroyed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "soup_auth_domain_set_generic_auth_callback" soup_auth_domain_set_generic_auth_callback :: 
    Ptr AuthDomain ->                       -- domain : TInterface (Name {namespace = "Soup", name = "AuthDomain"})
    FunPtr Soup.Callbacks.C_AuthDomainGenericAuthCallback -> -- auth_callback : TInterface (Name {namespace = "Soup", name = "AuthDomainGenericAuthCallback"})
    Ptr () ->                               -- auth_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- dnotify : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO ()

-- | Sets /@authCallback@/ as an authentication-handling callback for
-- /@domain@/. Whenever a request comes in to /@domain@/ which cannot be
-- authenticated via a domain-specific auth callback (eg,
-- t'GI.Soup.Callbacks.AuthDomainDigestAuthCallback'), the generic auth callback
-- will be invoked. See t'GI.Soup.Callbacks.AuthDomainGenericAuthCallback' for information
-- on what the callback should do.
authDomainSetGenericAuthCallback ::
    (B.CallStack.HasCallStack, MonadIO m, IsAuthDomain a) =>
    a
    -- ^ /@domain@/: a t'GI.Soup.Objects.AuthDomain.AuthDomain'
    -> Soup.Callbacks.AuthDomainGenericAuthCallback
    -- ^ /@authCallback@/: the auth callback
    -> m ()
authDomainSetGenericAuthCallback :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAuthDomain a) =>
a -> AuthDomainGenericAuthCallback -> m ()
authDomainSetGenericAuthCallback a
domain AuthDomainGenericAuthCallback
authCallback = 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 AuthDomain
domain' <- a -> IO (Ptr AuthDomain)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
domain
    FunPtr C_AuthDomainGenericAuthCallback
authCallback' <- C_AuthDomainGenericAuthCallback
-> IO (FunPtr C_AuthDomainGenericAuthCallback)
Soup.Callbacks.mk_AuthDomainGenericAuthCallback (Maybe (Ptr (FunPtr C_AuthDomainGenericAuthCallback))
-> AuthDomainGenericAuthCallback_WithClosures
-> C_AuthDomainGenericAuthCallback
Soup.Callbacks.wrap_AuthDomainGenericAuthCallback Maybe (Ptr (FunPtr C_AuthDomainGenericAuthCallback))
forall a. Maybe a
Nothing (AuthDomainGenericAuthCallback
-> AuthDomainGenericAuthCallback_WithClosures
Soup.Callbacks.drop_closures_AuthDomainGenericAuthCallback AuthDomainGenericAuthCallback
authCallback))
    let authData :: Ptr ()
authData = FunPtr C_AuthDomainGenericAuthCallback -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_AuthDomainGenericAuthCallback
authCallback'
    let dnotify :: FunPtr (Ptr a -> IO ())
dnotify = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    Ptr AuthDomain
-> FunPtr C_AuthDomainGenericAuthCallback
-> Ptr ()
-> FunPtr (Ptr () -> IO ())
-> IO ()
soup_auth_domain_set_generic_auth_callback Ptr AuthDomain
domain' FunPtr C_AuthDomainGenericAuthCallback
authCallback' Ptr ()
authData 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 AuthDomainSetGenericAuthCallbackMethodInfo
instance (signature ~ (Soup.Callbacks.AuthDomainGenericAuthCallback -> m ()), MonadIO m, IsAuthDomain a) => O.OverloadedMethod AuthDomainSetGenericAuthCallbackMethodInfo a signature where
    overloadedMethod = authDomainSetGenericAuthCallback

instance O.OverloadedMethodInfo AuthDomainSetGenericAuthCallbackMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.authDomainSetGenericAuthCallback",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#v:authDomainSetGenericAuthCallback"
        })


#endif

-- method AuthDomain::try_generic_auth_callback
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "domain"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "AuthDomain" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "msg"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "Message" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "username"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "soup_auth_domain_try_generic_auth_callback" soup_auth_domain_try_generic_auth_callback :: 
    Ptr AuthDomain ->                       -- domain : TInterface (Name {namespace = "Soup", name = "AuthDomain"})
    Ptr Soup.Message.Message ->             -- msg : TInterface (Name {namespace = "Soup", name = "Message"})
    CString ->                              -- username : TBasicType TUTF8
    IO CInt

-- | /No description available in the introspection data./
authDomainTryGenericAuthCallback ::
    (B.CallStack.HasCallStack, MonadIO m, IsAuthDomain a, Soup.Message.IsMessage b) =>
    a
    -> b
    -> T.Text
    -> m Bool
authDomainTryGenericAuthCallback :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsAuthDomain a, IsMessage b) =>
a -> b -> Text -> m Bool
authDomainTryGenericAuthCallback a
domain b
msg Text
username = 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 AuthDomain
domain' <- a -> IO (Ptr AuthDomain)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
domain
    Ptr Message
msg' <- b -> IO (Ptr Message)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
msg
    CString
username' <- Text -> IO CString
textToCString Text
username
    CInt
result <- Ptr AuthDomain -> Ptr Message -> CString -> IO CInt
soup_auth_domain_try_generic_auth_callback Ptr AuthDomain
domain' Ptr Message
msg' CString
username'
    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
domain
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
msg
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
username'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data AuthDomainTryGenericAuthCallbackMethodInfo
instance (signature ~ (b -> T.Text -> m Bool), MonadIO m, IsAuthDomain a, Soup.Message.IsMessage b) => O.OverloadedMethod AuthDomainTryGenericAuthCallbackMethodInfo a signature where
    overloadedMethod = authDomainTryGenericAuthCallback

instance O.OverloadedMethodInfo AuthDomainTryGenericAuthCallbackMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Soup.Objects.AuthDomain.authDomainTryGenericAuthCallback",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-soup-2.4.25/docs/GI-Soup-Objects-AuthDomain.html#v:authDomainTryGenericAuthCallback"
        })


#endif