{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- 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.AuthManager
    ( 

-- * Exported types
    AuthManager(..)                         ,
    IsAuthManager                           ,
    toAuthManager                           ,
    noAuthManager                           ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveAuthManagerMethod                ,
#endif


-- ** clearCachedCredentials #method:clearCachedCredentials#

#if defined(ENABLE_OVERLOADING)
    AuthManagerClearCachedCredentialsMethodInfo,
#endif
    authManagerClearCachedCredentials       ,


-- ** useAuth #method:useAuth#

#if defined(ENABLE_OVERLOADING)
    AuthManagerUseAuthMethodInfo            ,
#endif
    authManagerUseAuth                      ,




 -- * Signals
-- ** authenticate #signal:authenticate#

    AuthManagerAuthenticateCallback         ,
#if defined(ENABLE_OVERLOADING)
    AuthManagerAuthenticateSignalInfo       ,
#endif
    C_AuthManagerAuthenticateCallback       ,
    afterAuthManagerAuthenticate            ,
    genClosure_AuthManagerAuthenticate      ,
    mk_AuthManagerAuthenticateCallback      ,
    noAuthManagerAuthenticateCallback       ,
    onAuthManagerAuthenticate               ,
    wrap_AuthManagerAuthenticateCallback    ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Soup.Interfaces.SessionFeature as Soup.SessionFeature
import {-# SOURCE #-} qualified GI.Soup.Objects.Auth as Soup.Auth
import {-# SOURCE #-} qualified GI.Soup.Objects.Message as Soup.Message
import {-# SOURCE #-} qualified GI.Soup.Structs.URI as Soup.URI

-- | Memory-managed wrapper type.
newtype AuthManager = AuthManager (ManagedPtr AuthManager)
    deriving (AuthManager -> AuthManager -> Bool
(AuthManager -> AuthManager -> Bool)
-> (AuthManager -> AuthManager -> Bool) -> Eq AuthManager
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthManager -> AuthManager -> Bool
$c/= :: AuthManager -> AuthManager -> Bool
== :: AuthManager -> AuthManager -> Bool
$c== :: AuthManager -> AuthManager -> Bool
Eq)
foreign import ccall "soup_auth_manager_get_type"
    c_soup_auth_manager_get_type :: IO GType

instance GObject AuthManager where
    gobjectType :: IO GType
gobjectType = IO GType
c_soup_auth_manager_get_type
    

-- | Convert 'AuthManager' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue AuthManager where
    toGValue :: AuthManager -> IO GValue
toGValue o :: AuthManager
o = do
        GType
gtype <- IO GType
c_soup_auth_manager_get_type
        AuthManager -> (Ptr AuthManager -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AuthManager
o (GType
-> (GValue -> Ptr AuthManager -> IO ())
-> Ptr AuthManager
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr AuthManager -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO AuthManager
fromGValue gv :: GValue
gv = do
        Ptr AuthManager
ptr <- GValue -> IO (Ptr AuthManager)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr AuthManager)
        (ManagedPtr AuthManager -> AuthManager)
-> Ptr AuthManager -> IO AuthManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr AuthManager -> AuthManager
AuthManager Ptr AuthManager
ptr
        
    

-- | Type class for types which can be safely cast to `AuthManager`, for instance with `toAuthManager`.
class (GObject o, O.IsDescendantOf AuthManager o) => IsAuthManager o
instance (GObject o, O.IsDescendantOf AuthManager o) => IsAuthManager o

instance O.HasParentTypes AuthManager
type instance O.ParentTypes AuthManager = '[GObject.Object.Object, Soup.SessionFeature.SessionFeature]

-- | Cast to `AuthManager`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toAuthManager :: (MonadIO m, IsAuthManager o) => o -> m AuthManager
toAuthManager :: o -> m AuthManager
toAuthManager = IO AuthManager -> m AuthManager
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AuthManager -> m AuthManager)
-> (o -> IO AuthManager) -> o -> m AuthManager
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr AuthManager -> AuthManager) -> o -> IO AuthManager
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr AuthManager -> AuthManager
AuthManager

-- | A convenience alias for `Nothing` :: `Maybe` `AuthManager`.
noAuthManager :: Maybe AuthManager
noAuthManager :: Maybe AuthManager
noAuthManager = Maybe AuthManager
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveAuthManagerMethod (t :: Symbol) (o :: *) :: * where
    ResolveAuthManagerMethod "addFeature" o = Soup.SessionFeature.SessionFeatureAddFeatureMethodInfo
    ResolveAuthManagerMethod "attach" o = Soup.SessionFeature.SessionFeatureAttachMethodInfo
    ResolveAuthManagerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveAuthManagerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveAuthManagerMethod "clearCachedCredentials" o = AuthManagerClearCachedCredentialsMethodInfo
    ResolveAuthManagerMethod "detach" o = Soup.SessionFeature.SessionFeatureDetachMethodInfo
    ResolveAuthManagerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveAuthManagerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveAuthManagerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveAuthManagerMethod "hasFeature" o = Soup.SessionFeature.SessionFeatureHasFeatureMethodInfo
    ResolveAuthManagerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveAuthManagerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveAuthManagerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveAuthManagerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveAuthManagerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveAuthManagerMethod "removeFeature" o = Soup.SessionFeature.SessionFeatureRemoveFeatureMethodInfo
    ResolveAuthManagerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveAuthManagerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveAuthManagerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveAuthManagerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveAuthManagerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveAuthManagerMethod "useAuth" o = AuthManagerUseAuthMethodInfo
    ResolveAuthManagerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveAuthManagerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveAuthManagerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveAuthManagerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveAuthManagerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveAuthManagerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveAuthManagerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveAuthManagerMethod l o = O.MethodResolutionFailed l o

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

#endif

-- signal AuthManager::authenticate
-- | Emitted when the manager requires the application to
-- provide authentication credentials.
-- 
-- t'GI.Soup.Objects.Session.Session' connects to this signal and emits its own
-- [authenticate]("GI.Soup.Objects.Session#signal:authenticate") signal when it is emitted, so
-- you shouldn\'t need to use this signal directly.
type AuthManagerAuthenticateCallback =
    Soup.Message.Message
    -- ^ /@msg@/: the t'GI.Soup.Objects.Message.Message' being sent
    -> Soup.Auth.Auth
    -- ^ /@auth@/: the t'GI.Soup.Objects.Auth.Auth' to authenticate
    -> Bool
    -- ^ /@retrying@/: 'P.True' if this is the second (or later) attempt
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `AuthManagerAuthenticateCallback`@.
noAuthManagerAuthenticateCallback :: Maybe AuthManagerAuthenticateCallback
noAuthManagerAuthenticateCallback :: Maybe AuthManagerAuthenticateCallback
noAuthManagerAuthenticateCallback = Maybe AuthManagerAuthenticateCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_AuthManagerAuthenticateCallback =
    Ptr () ->                               -- object
    Ptr Soup.Message.Message ->
    Ptr Soup.Auth.Auth ->
    CInt ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_AuthManagerAuthenticateCallback`.
foreign import ccall "wrapper"
    mk_AuthManagerAuthenticateCallback :: C_AuthManagerAuthenticateCallback -> IO (FunPtr C_AuthManagerAuthenticateCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_AuthManagerAuthenticate :: MonadIO m => AuthManagerAuthenticateCallback -> m (GClosure C_AuthManagerAuthenticateCallback)
genClosure_AuthManagerAuthenticate :: AuthManagerAuthenticateCallback
-> m (GClosure C_AuthManagerAuthenticateCallback)
genClosure_AuthManagerAuthenticate cb :: AuthManagerAuthenticateCallback
cb = IO (GClosure C_AuthManagerAuthenticateCallback)
-> m (GClosure C_AuthManagerAuthenticateCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_AuthManagerAuthenticateCallback)
 -> m (GClosure C_AuthManagerAuthenticateCallback))
-> IO (GClosure C_AuthManagerAuthenticateCallback)
-> m (GClosure C_AuthManagerAuthenticateCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AuthManagerAuthenticateCallback
cb' = AuthManagerAuthenticateCallback
-> C_AuthManagerAuthenticateCallback
wrap_AuthManagerAuthenticateCallback AuthManagerAuthenticateCallback
cb
    C_AuthManagerAuthenticateCallback
-> IO (FunPtr C_AuthManagerAuthenticateCallback)
mk_AuthManagerAuthenticateCallback C_AuthManagerAuthenticateCallback
cb' IO (FunPtr C_AuthManagerAuthenticateCallback)
-> (FunPtr C_AuthManagerAuthenticateCallback
    -> IO (GClosure C_AuthManagerAuthenticateCallback))
-> IO (GClosure C_AuthManagerAuthenticateCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_AuthManagerAuthenticateCallback
-> IO (GClosure C_AuthManagerAuthenticateCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `AuthManagerAuthenticateCallback` into a `C_AuthManagerAuthenticateCallback`.
wrap_AuthManagerAuthenticateCallback ::
    AuthManagerAuthenticateCallback ->
    C_AuthManagerAuthenticateCallback
wrap_AuthManagerAuthenticateCallback :: AuthManagerAuthenticateCallback
-> C_AuthManagerAuthenticateCallback
wrap_AuthManagerAuthenticateCallback _cb :: AuthManagerAuthenticateCallback
_cb _ msg :: Ptr Message
msg auth :: Ptr Auth
auth retrying :: CInt
retrying _ = do
    Message
msg' <- ((ManagedPtr Message -> Message) -> Ptr Message -> IO Message
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Message -> Message
Soup.Message.Message) Ptr Message
msg
    Auth
auth' <- ((ManagedPtr Auth -> Auth) -> Ptr Auth -> IO Auth
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Auth -> Auth
Soup.Auth.Auth) Ptr Auth
auth
    let retrying' :: Bool
retrying' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
retrying
    AuthManagerAuthenticateCallback
_cb  Message
msg' Auth
auth' Bool
retrying'


-- | Connect a signal handler for the [authenticate](#signal:authenticate) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' authManager #authenticate callback
-- @
-- 
-- 
onAuthManagerAuthenticate :: (IsAuthManager a, MonadIO m) => a -> AuthManagerAuthenticateCallback -> m SignalHandlerId
onAuthManagerAuthenticate :: a -> AuthManagerAuthenticateCallback -> m SignalHandlerId
onAuthManagerAuthenticate obj :: a
obj cb :: AuthManagerAuthenticateCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AuthManagerAuthenticateCallback
cb' = AuthManagerAuthenticateCallback
-> C_AuthManagerAuthenticateCallback
wrap_AuthManagerAuthenticateCallback AuthManagerAuthenticateCallback
cb
    FunPtr C_AuthManagerAuthenticateCallback
cb'' <- C_AuthManagerAuthenticateCallback
-> IO (FunPtr C_AuthManagerAuthenticateCallback)
mk_AuthManagerAuthenticateCallback C_AuthManagerAuthenticateCallback
cb'
    a
-> Text
-> FunPtr C_AuthManagerAuthenticateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "authenticate" FunPtr C_AuthManagerAuthenticateCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [authenticate](#signal:authenticate) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' authManager #authenticate callback
-- @
-- 
-- 
afterAuthManagerAuthenticate :: (IsAuthManager a, MonadIO m) => a -> AuthManagerAuthenticateCallback -> m SignalHandlerId
afterAuthManagerAuthenticate :: a -> AuthManagerAuthenticateCallback -> m SignalHandlerId
afterAuthManagerAuthenticate obj :: a
obj cb :: AuthManagerAuthenticateCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AuthManagerAuthenticateCallback
cb' = AuthManagerAuthenticateCallback
-> C_AuthManagerAuthenticateCallback
wrap_AuthManagerAuthenticateCallback AuthManagerAuthenticateCallback
cb
    FunPtr C_AuthManagerAuthenticateCallback
cb'' <- C_AuthManagerAuthenticateCallback
-> IO (FunPtr C_AuthManagerAuthenticateCallback)
mk_AuthManagerAuthenticateCallback C_AuthManagerAuthenticateCallback
cb'
    a
-> Text
-> FunPtr C_AuthManagerAuthenticateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "authenticate" FunPtr C_AuthManagerAuthenticateCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data AuthManagerAuthenticateSignalInfo
instance SignalInfo AuthManagerAuthenticateSignalInfo where
    type HaskellCallbackType AuthManagerAuthenticateSignalInfo = AuthManagerAuthenticateCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_AuthManagerAuthenticateCallback cb
        cb'' <- mk_AuthManagerAuthenticateCallback cb'
        connectSignalFunPtr obj "authenticate" cb'' connectMode detail

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AuthManager
type instance O.AttributeList AuthManager = AuthManagerAttributeList
type AuthManagerAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method AuthManager::clear_cached_credentials
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "AuthManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #SoupAuthManager" , 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_manager_clear_cached_credentials" soup_auth_manager_clear_cached_credentials :: 
    Ptr AuthManager ->                      -- manager : TInterface (Name {namespace = "Soup", name = "AuthManager"})
    IO ()

-- | Clear all credentials cached by /@manager@/
-- 
-- /Since: 2.58/
authManagerClearCachedCredentials ::
    (B.CallStack.HasCallStack, MonadIO m, IsAuthManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Soup.Objects.AuthManager.AuthManager'
    -> m ()
authManagerClearCachedCredentials :: a -> m ()
authManagerClearCachedCredentials manager :: a
manager = 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 AuthManager
manager' <- a -> IO (Ptr AuthManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr AuthManager -> IO ()
soup_auth_manager_clear_cached_credentials Ptr AuthManager
manager'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AuthManagerClearCachedCredentialsMethodInfo
instance (signature ~ (m ()), MonadIO m, IsAuthManager a) => O.MethodInfo AuthManagerClearCachedCredentialsMethodInfo a signature where
    overloadedMethod = authManagerClearCachedCredentials

#endif

-- method AuthManager::use_auth
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Soup" , name = "AuthManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #SoupAuthManager" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TInterface Name { namespace = "Soup" , name = "URI" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #SoupURI under which @auth is to be used"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "auth"
--           , argType = TInterface Name { namespace = "Soup" , name = "Auth" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #SoupAuth to use"
--                 , 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_manager_use_auth" soup_auth_manager_use_auth :: 
    Ptr AuthManager ->                      -- manager : TInterface (Name {namespace = "Soup", name = "AuthManager"})
    Ptr Soup.URI.URI ->                     -- uri : TInterface (Name {namespace = "Soup", name = "URI"})
    Ptr Soup.Auth.Auth ->                   -- auth : TInterface (Name {namespace = "Soup", name = "Auth"})
    IO ()

-- | Records that /@auth@/ is to be used under /@uri@/, as though a
-- WWW-Authenticate header had been received at that URI. This can be
-- used to \"preload\" /@manager@/\'s auth cache, to avoid an extra HTTP
-- round trip in the case where you know ahead of time that a 401
-- response will be returned.
-- 
-- This is only useful for authentication types where the initial
-- Authorization header does not depend on any additional information
-- from the server. (Eg, Basic or NTLM, but not Digest.)
-- 
-- /Since: 2.42/
authManagerUseAuth ::
    (B.CallStack.HasCallStack, MonadIO m, IsAuthManager a, Soup.Auth.IsAuth b) =>
    a
    -- ^ /@manager@/: a t'GI.Soup.Objects.AuthManager.AuthManager'
    -> Soup.URI.URI
    -- ^ /@uri@/: the t'GI.Soup.Structs.URI.URI' under which /@auth@/ is to be used
    -> b
    -- ^ /@auth@/: the t'GI.Soup.Objects.Auth.Auth' to use
    -> m ()
authManagerUseAuth :: a -> URI -> b -> m ()
authManagerUseAuth manager :: a
manager uri :: URI
uri auth :: b
auth = 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 AuthManager
manager' <- a -> IO (Ptr AuthManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr URI
uri' <- URI -> IO (Ptr URI)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr URI
uri
    Ptr Auth
auth' <- b -> IO (Ptr Auth)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
auth
    Ptr AuthManager -> Ptr URI -> Ptr Auth -> IO ()
soup_auth_manager_use_auth Ptr AuthManager
manager' Ptr URI
uri' Ptr Auth
auth'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    URI -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr URI
uri
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
auth
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AuthManagerUseAuthMethodInfo
instance (signature ~ (Soup.URI.URI -> b -> m ()), MonadIO m, IsAuthManager a, Soup.Auth.IsAuth b) => O.MethodInfo AuthManagerUseAuthMethodInfo a signature where
    overloadedMethod = authManagerUseAuth

#endif