{-# 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.AuthNTLM
    ( 

-- * Exported types
    AuthNTLM(..)                            ,
    IsAuthNTLM                              ,
    toAuthNTLM                              ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [authenticate]("GI.Soup.Objects.Auth#g:method:authenticate"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [canAuthenticate]("GI.Soup.Objects.Auth#g:method:canAuthenticate"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hasSavedPassword]("GI.Soup.Objects.Auth#g:method:hasSavedPassword"), [isAuthenticated]("GI.Soup.Objects.Auth#g:method:isAuthenticated"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isForProxy]("GI.Soup.Objects.Auth#g:method:isForProxy"), [isReady]("GI.Soup.Objects.Auth#g:method:isReady"), [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"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [savePassword]("GI.Soup.Objects.Auth#g:method:savePassword"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [update]("GI.Soup.Objects.Auth#g:method:update"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAuthorization]("GI.Soup.Objects.Auth#g:method:getAuthorization"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getHost]("GI.Soup.Objects.Auth#g:method:getHost"), [getInfo]("GI.Soup.Objects.Auth#g:method:getInfo"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getProtectionSpace]("GI.Soup.Objects.Auth#g:method:getProtectionSpace"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRealm]("GI.Soup.Objects.Auth#g:method:getRealm"), [getSavedPassword]("GI.Soup.Objects.Auth#g:method:getSavedPassword"), [getSavedUsers]("GI.Soup.Objects.Auth#g:method:getSavedUsers"), [getSchemeName]("GI.Soup.Objects.Auth#g:method:getSchemeName").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveAuthNTLMMethod                   ,
#endif



    ) 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.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Soup.Objects.Auth as Soup.Auth

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

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

foreign import ccall "soup_auth_ntlm_get_type"
    c_soup_auth_ntlm_get_type :: IO B.Types.GType

instance B.Types.TypedObject AuthNTLM where
    glibType :: IO GType
glibType = IO GType
c_soup_auth_ntlm_get_type

instance B.Types.GObject AuthNTLM

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

instance O.HasParentTypes AuthNTLM
type instance O.ParentTypes AuthNTLM = '[Soup.Auth.Auth, GObject.Object.Object]

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

-- | Convert 'AuthNTLM' 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 AuthNTLM) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_soup_auth_ntlm_get_type
    gvalueSet_ :: Ptr GValue -> Maybe AuthNTLM -> IO ()
gvalueSet_ Ptr GValue
gv Maybe AuthNTLM
P.Nothing = Ptr GValue -> Ptr AuthNTLM -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr AuthNTLM
forall a. Ptr a
FP.nullPtr :: FP.Ptr AuthNTLM)
    gvalueSet_ Ptr GValue
gv (P.Just AuthNTLM
obj) = AuthNTLM -> (Ptr AuthNTLM -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AuthNTLM
obj (Ptr GValue -> Ptr AuthNTLM -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe AuthNTLM)
gvalueGet_ Ptr GValue
gv = do
        Ptr AuthNTLM
ptr <- Ptr GValue -> IO (Ptr AuthNTLM)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr AuthNTLM)
        if Ptr AuthNTLM
ptr Ptr AuthNTLM -> Ptr AuthNTLM -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr AuthNTLM
forall a. Ptr a
FP.nullPtr
        then AuthNTLM -> Maybe AuthNTLM
forall a. a -> Maybe a
P.Just (AuthNTLM -> Maybe AuthNTLM) -> IO AuthNTLM -> IO (Maybe AuthNTLM)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr AuthNTLM -> AuthNTLM) -> Ptr AuthNTLM -> IO AuthNTLM
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr AuthNTLM -> AuthNTLM
AuthNTLM Ptr AuthNTLM
ptr
        else Maybe AuthNTLM -> IO (Maybe AuthNTLM)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AuthNTLM
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveAuthNTLMMethod (t :: Symbol) (o :: *) :: * where
    ResolveAuthNTLMMethod "authenticate" o = Soup.Auth.AuthAuthenticateMethodInfo
    ResolveAuthNTLMMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveAuthNTLMMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveAuthNTLMMethod "canAuthenticate" o = Soup.Auth.AuthCanAuthenticateMethodInfo
    ResolveAuthNTLMMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveAuthNTLMMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveAuthNTLMMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveAuthNTLMMethod "hasSavedPassword" o = Soup.Auth.AuthHasSavedPasswordMethodInfo
    ResolveAuthNTLMMethod "isAuthenticated" o = Soup.Auth.AuthIsAuthenticatedMethodInfo
    ResolveAuthNTLMMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveAuthNTLMMethod "isForProxy" o = Soup.Auth.AuthIsForProxyMethodInfo
    ResolveAuthNTLMMethod "isReady" o = Soup.Auth.AuthIsReadyMethodInfo
    ResolveAuthNTLMMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveAuthNTLMMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveAuthNTLMMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveAuthNTLMMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveAuthNTLMMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveAuthNTLMMethod "savePassword" o = Soup.Auth.AuthSavePasswordMethodInfo
    ResolveAuthNTLMMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveAuthNTLMMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveAuthNTLMMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveAuthNTLMMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveAuthNTLMMethod "update" o = Soup.Auth.AuthUpdateMethodInfo
    ResolveAuthNTLMMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveAuthNTLMMethod "getAuthorization" o = Soup.Auth.AuthGetAuthorizationMethodInfo
    ResolveAuthNTLMMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveAuthNTLMMethod "getHost" o = Soup.Auth.AuthGetHostMethodInfo
    ResolveAuthNTLMMethod "getInfo" o = Soup.Auth.AuthGetInfoMethodInfo
    ResolveAuthNTLMMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveAuthNTLMMethod "getProtectionSpace" o = Soup.Auth.AuthGetProtectionSpaceMethodInfo
    ResolveAuthNTLMMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveAuthNTLMMethod "getRealm" o = Soup.Auth.AuthGetRealmMethodInfo
    ResolveAuthNTLMMethod "getSavedPassword" o = Soup.Auth.AuthGetSavedPasswordMethodInfo
    ResolveAuthNTLMMethod "getSavedUsers" o = Soup.Auth.AuthGetSavedUsersMethodInfo
    ResolveAuthNTLMMethod "getSchemeName" o = Soup.Auth.AuthGetSchemeNameMethodInfo
    ResolveAuthNTLMMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveAuthNTLMMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveAuthNTLMMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveAuthNTLMMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveAuthNTLMMethod t AuthNTLM, O.OverloadedMethod info AuthNTLM p) => OL.IsLabel t (AuthNTLM -> 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 ~ ResolveAuthNTLMMethod t AuthNTLM, O.OverloadedMethod info AuthNTLM p, R.HasField t AuthNTLM p) => R.HasField t AuthNTLM p where
    getField = O.overloadedMethod @info

#endif

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

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AuthNTLM
type instance O.AttributeList AuthNTLM = AuthNTLMAttributeList
type AuthNTLMAttributeList = ('[ '("host", Soup.Auth.AuthHostPropertyInfo), '("isAuthenticated", Soup.Auth.AuthIsAuthenticatedPropertyInfo), '("isForProxy", Soup.Auth.AuthIsForProxyPropertyInfo), '("realm", Soup.Auth.AuthRealmPropertyInfo), '("schemeName", Soup.Auth.AuthSchemeNamePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif