{-# 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./
-- 
-- /Since: 1.6/

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

module GI.NM.Structs.DnsEntry
    ( 

-- * Exported types
    DnsEntry(..)                            ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [unref]("GI.NM.Structs.DnsEntry#g:method:unref").
-- 
-- ==== Getters
-- [getDomains]("GI.NM.Structs.DnsEntry#g:method:getDomains"), [getInterface]("GI.NM.Structs.DnsEntry#g:method:getInterface"), [getNameservers]("GI.NM.Structs.DnsEntry#g:method:getNameservers"), [getPriority]("GI.NM.Structs.DnsEntry#g:method:getPriority"), [getVpn]("GI.NM.Structs.DnsEntry#g:method:getVpn").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveDnsEntryMethod                   ,
#endif

-- ** getDomains #method:getDomains#

#if defined(ENABLE_OVERLOADING)
    DnsEntryGetDomainsMethodInfo            ,
#endif
    dnsEntryGetDomains                      ,


-- ** getInterface #method:getInterface#

#if defined(ENABLE_OVERLOADING)
    DnsEntryGetInterfaceMethodInfo          ,
#endif
    dnsEntryGetInterface                    ,


-- ** getNameservers #method:getNameservers#

#if defined(ENABLE_OVERLOADING)
    DnsEntryGetNameserversMethodInfo        ,
#endif
    dnsEntryGetNameservers                  ,


-- ** getPriority #method:getPriority#

#if defined(ENABLE_OVERLOADING)
    DnsEntryGetPriorityMethodInfo           ,
#endif
    dnsEntryGetPriority                     ,


-- ** getVpn #method:getVpn#

#if defined(ENABLE_OVERLOADING)
    DnsEntryGetVpnMethodInfo                ,
#endif
    dnsEntryGetVpn                          ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    DnsEntryUnrefMethodInfo                 ,
#endif
    dnsEntryUnref                           ,




    ) 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.GHashTable as B.GHT
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.Kind as DK
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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)

#else

#endif

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

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

foreign import ccall "nm_dns_entry_get_type" c_nm_dns_entry_get_type :: 
    IO GType

type instance O.ParentTypes DnsEntry = '[]
instance O.HasParentTypes DnsEntry

instance B.Types.TypedObject DnsEntry where
    glibType :: IO GType
glibType = IO GType
c_nm_dns_entry_get_type

instance B.Types.GBoxed DnsEntry

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


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DnsEntry
type instance O.AttributeList DnsEntry = DnsEntryAttributeList
type DnsEntryAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

-- method DnsEntry::get_domains
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "entry"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "DnsEntry" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMDnsEntry" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "nm_dns_entry_get_domains" nm_dns_entry_get_domains :: 
    Ptr DnsEntry ->                         -- entry : TInterface (Name {namespace = "NM", name = "DnsEntry"})
    IO (Ptr CString)

-- | Gets the list of DNS domains.
-- 
-- /Since: 1.6/
dnsEntryGetDomains ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    DnsEntry
    -- ^ /@entry@/: the t'GI.NM.Structs.DnsEntry.DnsEntry'
    -> m [T.Text]
    -- ^ __Returns:__ the list of DNS domains
dnsEntryGetDomains :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
DnsEntry -> m [Text]
dnsEntryGetDomains DnsEntry
entry = IO [Text] -> m [Text]
forall a. IO a -> m a
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 DnsEntry
entry' <- DnsEntry -> IO (Ptr DnsEntry)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DnsEntry
entry
    Ptr CString
result <- Ptr DnsEntry -> IO (Ptr CString)
nm_dns_entry_get_domains Ptr DnsEntry
entry'
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dnsEntryGetDomains" Ptr CString
result
    [Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
    DnsEntry -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DnsEntry
entry
    [Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

#if defined(ENABLE_OVERLOADING)
data DnsEntryGetDomainsMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m) => O.OverloadedMethod DnsEntryGetDomainsMethodInfo DnsEntry signature where
    overloadedMethod = dnsEntryGetDomains

instance O.OverloadedMethodInfo DnsEntryGetDomainsMethodInfo DnsEntry where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Structs.DnsEntry.dnsEntryGetDomains",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Structs-DnsEntry.html#v:dnsEntryGetDomains"
        })


#endif

-- method DnsEntry::get_interface
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "entry"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "DnsEntry" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMDnsEntry" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "nm_dns_entry_get_interface" nm_dns_entry_get_interface :: 
    Ptr DnsEntry ->                         -- entry : TInterface (Name {namespace = "NM", name = "DnsEntry"})
    IO CString

-- | Gets the interface on which name servers are contacted.
-- 
-- /Since: 1.6/
dnsEntryGetInterface ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    DnsEntry
    -- ^ /@entry@/: the t'GI.NM.Structs.DnsEntry.DnsEntry'
    -> m T.Text
    -- ^ __Returns:__ the interface name
dnsEntryGetInterface :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
DnsEntry -> m Text
dnsEntryGetInterface DnsEntry
entry = IO Text -> m Text
forall a. IO a -> m a
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 DnsEntry
entry' <- DnsEntry -> IO (Ptr DnsEntry)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DnsEntry
entry
    CString
result <- Ptr DnsEntry -> IO CString
nm_dns_entry_get_interface Ptr DnsEntry
entry'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dnsEntryGetInterface" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    DnsEntry -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DnsEntry
entry
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DnsEntryGetInterfaceMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod DnsEntryGetInterfaceMethodInfo DnsEntry signature where
    overloadedMethod = dnsEntryGetInterface

instance O.OverloadedMethodInfo DnsEntryGetInterfaceMethodInfo DnsEntry where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Structs.DnsEntry.dnsEntryGetInterface",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Structs-DnsEntry.html#v:dnsEntryGetInterface"
        })


#endif

-- method DnsEntry::get_nameservers
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "entry"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "DnsEntry" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMDnsEntry" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "nm_dns_entry_get_nameservers" nm_dns_entry_get_nameservers :: 
    Ptr DnsEntry ->                         -- entry : TInterface (Name {namespace = "NM", name = "DnsEntry"})
    IO (Ptr CString)

-- | Gets the list of name servers for this entry.
-- 
-- /Since: 1.6/
dnsEntryGetNameservers ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    DnsEntry
    -- ^ /@entry@/: the t'GI.NM.Structs.DnsEntry.DnsEntry'
    -> m [T.Text]
    -- ^ __Returns:__ the list of name servers
dnsEntryGetNameservers :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
DnsEntry -> m [Text]
dnsEntryGetNameservers DnsEntry
entry = IO [Text] -> m [Text]
forall a. IO a -> m a
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 DnsEntry
entry' <- DnsEntry -> IO (Ptr DnsEntry)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DnsEntry
entry
    Ptr CString
result <- Ptr DnsEntry -> IO (Ptr CString)
nm_dns_entry_get_nameservers Ptr DnsEntry
entry'
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dnsEntryGetNameservers" Ptr CString
result
    [Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
    DnsEntry -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DnsEntry
entry
    [Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

#if defined(ENABLE_OVERLOADING)
data DnsEntryGetNameserversMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m) => O.OverloadedMethod DnsEntryGetNameserversMethodInfo DnsEntry signature where
    overloadedMethod = dnsEntryGetNameservers

instance O.OverloadedMethodInfo DnsEntryGetNameserversMethodInfo DnsEntry where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Structs.DnsEntry.dnsEntryGetNameservers",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Structs-DnsEntry.html#v:dnsEntryGetNameservers"
        })


#endif

-- method DnsEntry::get_priority
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "entry"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "DnsEntry" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMDnsEntry" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "nm_dns_entry_get_priority" nm_dns_entry_get_priority :: 
    Ptr DnsEntry ->                         -- entry : TInterface (Name {namespace = "NM", name = "DnsEntry"})
    IO Int32

-- | Gets the priority of the entry
-- 
-- /Since: 1.6/
dnsEntryGetPriority ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    DnsEntry
    -- ^ /@entry@/: the t'GI.NM.Structs.DnsEntry.DnsEntry'
    -> m Int32
    -- ^ __Returns:__ the priority of the entry
dnsEntryGetPriority :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
DnsEntry -> m Int32
dnsEntryGetPriority DnsEntry
entry = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr DnsEntry
entry' <- DnsEntry -> IO (Ptr DnsEntry)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DnsEntry
entry
    Int32
result <- Ptr DnsEntry -> IO Int32
nm_dns_entry_get_priority Ptr DnsEntry
entry'
    DnsEntry -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DnsEntry
entry
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data DnsEntryGetPriorityMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod DnsEntryGetPriorityMethodInfo DnsEntry signature where
    overloadedMethod = dnsEntryGetPriority

instance O.OverloadedMethodInfo DnsEntryGetPriorityMethodInfo DnsEntry where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Structs.DnsEntry.dnsEntryGetPriority",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Structs-DnsEntry.html#v:dnsEntryGetPriority"
        })


#endif

-- method DnsEntry::get_vpn
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "entry"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "DnsEntry" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMDnsEntry" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "nm_dns_entry_get_vpn" nm_dns_entry_get_vpn :: 
    Ptr DnsEntry ->                         -- entry : TInterface (Name {namespace = "NM", name = "DnsEntry"})
    IO CInt

-- | Gets whether the entry refers to VPN name servers.
-- 
-- /Since: 1.6/
dnsEntryGetVpn ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    DnsEntry
    -- ^ /@entry@/: the t'GI.NM.Structs.DnsEntry.DnsEntry'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the entry refers to VPN name servers
dnsEntryGetVpn :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
DnsEntry -> m Bool
dnsEntryGetVpn DnsEntry
entry = IO Bool -> m Bool
forall a. IO a -> m a
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 DnsEntry
entry' <- DnsEntry -> IO (Ptr DnsEntry)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DnsEntry
entry
    CInt
result <- Ptr DnsEntry -> IO CInt
nm_dns_entry_get_vpn Ptr DnsEntry
entry'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    DnsEntry -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DnsEntry
entry
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DnsEntryGetVpnMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod DnsEntryGetVpnMethodInfo DnsEntry signature where
    overloadedMethod = dnsEntryGetVpn

instance O.OverloadedMethodInfo DnsEntryGetVpnMethodInfo DnsEntry where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Structs.DnsEntry.dnsEntryGetVpn",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Structs-DnsEntry.html#v:dnsEntryGetVpn"
        })


#endif

-- method DnsEntry::unref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "entry"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "DnsEntry" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMDnsEntry" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "nm_dns_entry_unref" nm_dns_entry_unref :: 
    Ptr DnsEntry ->                         -- entry : TInterface (Name {namespace = "NM", name = "DnsEntry"})
    IO ()

-- | Decreases the reference count of the object.  If the reference count
-- reaches zero, the object will be destroyed.
-- 
-- /Since: 1.6/
dnsEntryUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    DnsEntry
    -- ^ /@entry@/: the t'GI.NM.Structs.DnsEntry.DnsEntry'
    -> m ()
dnsEntryUnref :: forall (m :: * -> *). (HasCallStack, MonadIO m) => DnsEntry -> m ()
dnsEntryUnref DnsEntry
entry = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DnsEntry
entry' <- DnsEntry -> IO (Ptr DnsEntry)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DnsEntry
entry
    Ptr DnsEntry -> IO ()
nm_dns_entry_unref Ptr DnsEntry
entry'
    DnsEntry -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DnsEntry
entry
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DnsEntryUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod DnsEntryUnrefMethodInfo DnsEntry signature where
    overloadedMethod = dnsEntryUnref

instance O.OverloadedMethodInfo DnsEntryUnrefMethodInfo DnsEntry where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Structs.DnsEntry.dnsEntryUnref",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Structs-DnsEntry.html#v:dnsEntryUnref"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveDnsEntryMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveDnsEntryMethod "unref" o = DnsEntryUnrefMethodInfo
    ResolveDnsEntryMethod "getDomains" o = DnsEntryGetDomainsMethodInfo
    ResolveDnsEntryMethod "getInterface" o = DnsEntryGetInterfaceMethodInfo
    ResolveDnsEntryMethod "getNameservers" o = DnsEntryGetNameserversMethodInfo
    ResolveDnsEntryMethod "getPriority" o = DnsEntryGetPriorityMethodInfo
    ResolveDnsEntryMethod "getVpn" o = DnsEntryGetVpnMethodInfo
    ResolveDnsEntryMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif