{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Bluetooth Settings

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

module GI.NM.Objects.SettingBluetooth
    ( 

-- * Exported types
    SettingBluetooth(..)                    ,
    IsSettingBluetooth                      ,
    toSettingBluetooth                      ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [compare]("GI.NM.Objects.Setting#g:method:compare"), [diff]("GI.NM.Objects.Setting#g:method:diff"), [duplicate]("GI.NM.Objects.Setting#g:method:duplicate"), [enumerateValues]("GI.NM.Objects.Setting#g:method:enumerateValues"), [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"), [optionClearByName]("GI.NM.Objects.Setting#g:method:optionClearByName"), [optionGet]("GI.NM.Objects.Setting#g:method:optionGet"), [optionGetAllNames]("GI.NM.Objects.Setting#g:method:optionGetAllNames"), [optionGetBoolean]("GI.NM.Objects.Setting#g:method:optionGetBoolean"), [optionGetUint32]("GI.NM.Objects.Setting#g:method:optionGetUint32"), [optionSet]("GI.NM.Objects.Setting#g:method:optionSet"), [optionSetBoolean]("GI.NM.Objects.Setting#g:method:optionSetBoolean"), [optionSetUint32]("GI.NM.Objects.Setting#g:method:optionSetUint32"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [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"), [toString]("GI.NM.Objects.Setting#g:method:toString"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [verify]("GI.NM.Objects.Setting#g:method:verify"), [verifySecrets]("GI.NM.Objects.Setting#g:method:verifySecrets"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getBdaddr]("GI.NM.Objects.SettingBluetooth#g:method:getBdaddr"), [getConnectionType]("GI.NM.Objects.SettingBluetooth#g:method:getConnectionType"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDbusPropertyType]("GI.NM.Objects.Setting#g:method:getDbusPropertyType"), [getName]("GI.NM.Objects.Setting#g:method:getName"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSecretFlags]("GI.NM.Objects.Setting#g:method:getSecretFlags").
-- 
-- ==== 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"), [setSecretFlags]("GI.NM.Objects.Setting#g:method:setSecretFlags").

#if defined(ENABLE_OVERLOADING)
    ResolveSettingBluetoothMethod           ,
#endif

-- ** getBdaddr #method:getBdaddr#

#if defined(ENABLE_OVERLOADING)
    SettingBluetoothGetBdaddrMethodInfo     ,
#endif
    settingBluetoothGetBdaddr               ,


-- ** getConnectionType #method:getConnectionType#

#if defined(ENABLE_OVERLOADING)
    SettingBluetoothGetConnectionTypeMethodInfo,
#endif
    settingBluetoothGetConnectionType       ,


-- ** new #method:new#

    settingBluetoothNew                     ,




 -- * Properties


-- ** bdaddr #attr:bdaddr#
-- | The Bluetooth address of the device.

#if defined(ENABLE_OVERLOADING)
    SettingBluetoothBdaddrPropertyInfo      ,
#endif
    clearSettingBluetoothBdaddr             ,
    constructSettingBluetoothBdaddr         ,
    getSettingBluetoothBdaddr               ,
    setSettingBluetoothBdaddr               ,
#if defined(ENABLE_OVERLOADING)
    settingBluetoothBdaddr                  ,
#endif


-- ** type #attr:type#
-- | Either \"dun\" for Dial-Up Networking connections or \"panu\" for Personal
-- Area Networking connections to devices supporting the NAP profile.

#if defined(ENABLE_OVERLOADING)
    SettingBluetoothTypePropertyInfo        ,
#endif
    clearSettingBluetoothType               ,
    constructSettingBluetoothType           ,
    getSettingBluetoothType                 ,
    setSettingBluetoothType                 ,
#if defined(ENABLE_OVERLOADING)
    settingBluetoothType                    ,
#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.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)
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.VariantType as GLib.VariantType
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.NM.Callbacks as NM.Callbacks
import {-# SOURCE #-} qualified GI.NM.Enums as NM.Enums
import {-# SOURCE #-} qualified GI.NM.Flags as NM.Flags
import {-# SOURCE #-} qualified GI.NM.Interfaces.Connection as NM.Connection
import {-# SOURCE #-} qualified GI.NM.Objects.Setting as NM.Setting
import {-# SOURCE #-} qualified GI.NM.Objects.Setting8021x as NM.Setting8021x
import {-# SOURCE #-} qualified GI.NM.Objects.SettingAdsl as NM.SettingAdsl
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBond as NM.SettingBond
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBridge as NM.SettingBridge
import {-# SOURCE #-} qualified GI.NM.Objects.SettingBridgePort as NM.SettingBridgePort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingCdma as NM.SettingCdma
import {-# SOURCE #-} qualified GI.NM.Objects.SettingConnection as NM.SettingConnection
import {-# SOURCE #-} qualified GI.NM.Objects.SettingDcb as NM.SettingDcb
import {-# SOURCE #-} qualified GI.NM.Objects.SettingDummy as NM.SettingDummy
import {-# SOURCE #-} qualified GI.NM.Objects.SettingGeneric as NM.SettingGeneric
import {-# SOURCE #-} qualified GI.NM.Objects.SettingGsm as NM.SettingGsm
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIP4Config as NM.SettingIP4Config
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIP6Config as NM.SettingIP6Config
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIPConfig as NM.SettingIPConfig
import {-# SOURCE #-} qualified GI.NM.Objects.SettingIPTunnel as NM.SettingIPTunnel
import {-# SOURCE #-} qualified GI.NM.Objects.SettingInfiniband as NM.SettingInfiniband
import {-# SOURCE #-} qualified GI.NM.Objects.SettingMacsec as NM.SettingMacsec
import {-# SOURCE #-} qualified GI.NM.Objects.SettingMacvlan as NM.SettingMacvlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOlpcMesh as NM.SettingOlpcMesh
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsBridge as NM.SettingOvsBridge
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsInterface as NM.SettingOvsInterface
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsPatch as NM.SettingOvsPatch
import {-# SOURCE #-} qualified GI.NM.Objects.SettingOvsPort as NM.SettingOvsPort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingPpp as NM.SettingPpp
import {-# SOURCE #-} qualified GI.NM.Objects.SettingPppoe as NM.SettingPppoe
import {-# SOURCE #-} qualified GI.NM.Objects.SettingProxy as NM.SettingProxy
import {-# SOURCE #-} qualified GI.NM.Objects.SettingSerial as NM.SettingSerial
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTCConfig as NM.SettingTCConfig
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTeam as NM.SettingTeam
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTeamPort as NM.SettingTeamPort
import {-# SOURCE #-} qualified GI.NM.Objects.SettingTun as NM.SettingTun
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVlan as NM.SettingVlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVpn as NM.SettingVpn
import {-# SOURCE #-} qualified GI.NM.Objects.SettingVxlan as NM.SettingVxlan
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWimax as NM.SettingWimax
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWired as NM.SettingWired
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWireless as NM.SettingWireless
import {-# SOURCE #-} qualified GI.NM.Objects.SettingWirelessSecurity as NM.SettingWirelessSecurity
import {-# SOURCE #-} qualified GI.NM.Structs.BridgeVlan as NM.BridgeVlan
import {-# SOURCE #-} qualified GI.NM.Structs.IPAddress as NM.IPAddress
import {-# SOURCE #-} qualified GI.NM.Structs.IPRoute as NM.IPRoute
import {-# SOURCE #-} qualified GI.NM.Structs.IPRoutingRule as NM.IPRoutingRule
import {-# SOURCE #-} qualified GI.NM.Structs.Range as NM.Range
import {-# SOURCE #-} qualified GI.NM.Structs.TCAction as NM.TCAction
import {-# SOURCE #-} qualified GI.NM.Structs.TCQdisc as NM.TCQdisc
import {-# SOURCE #-} qualified GI.NM.Structs.TCTfilter as NM.TCTfilter
import {-# SOURCE #-} qualified GI.NM.Structs.TeamLinkWatcher as NM.TeamLinkWatcher
import {-# SOURCE #-} qualified GI.NM.Structs.VariantAttributeSpec as NM.VariantAttributeSpec

#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.NM.Objects.Setting as NM.Setting

#endif

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

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

foreign import ccall "nm_setting_bluetooth_get_type"
    c_nm_setting_bluetooth_get_type :: IO B.Types.GType

instance B.Types.TypedObject SettingBluetooth where
    glibType :: IO GType
glibType = IO GType
c_nm_setting_bluetooth_get_type

instance B.Types.GObject SettingBluetooth

-- | Type class for types which can be safely cast to t'SettingBluetooth', for instance with `toSettingBluetooth`.
class (SP.GObject o, O.IsDescendantOf SettingBluetooth o) => IsSettingBluetooth o
instance (SP.GObject o, O.IsDescendantOf SettingBluetooth o) => IsSettingBluetooth o

instance O.HasParentTypes SettingBluetooth
type instance O.ParentTypes SettingBluetooth = '[NM.Setting.Setting, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveSettingBluetoothMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveSettingBluetoothMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSettingBluetoothMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSettingBluetoothMethod "compare" o = NM.Setting.SettingCompareMethodInfo
    ResolveSettingBluetoothMethod "diff" o = NM.Setting.SettingDiffMethodInfo
    ResolveSettingBluetoothMethod "duplicate" o = NM.Setting.SettingDuplicateMethodInfo
    ResolveSettingBluetoothMethod "enumerateValues" o = NM.Setting.SettingEnumerateValuesMethodInfo
    ResolveSettingBluetoothMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSettingBluetoothMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSettingBluetoothMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSettingBluetoothMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSettingBluetoothMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSettingBluetoothMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSettingBluetoothMethod "optionClearByName" o = NM.Setting.SettingOptionClearByNameMethodInfo
    ResolveSettingBluetoothMethod "optionGet" o = NM.Setting.SettingOptionGetMethodInfo
    ResolveSettingBluetoothMethod "optionGetAllNames" o = NM.Setting.SettingOptionGetAllNamesMethodInfo
    ResolveSettingBluetoothMethod "optionGetBoolean" o = NM.Setting.SettingOptionGetBooleanMethodInfo
    ResolveSettingBluetoothMethod "optionGetUint32" o = NM.Setting.SettingOptionGetUint32MethodInfo
    ResolveSettingBluetoothMethod "optionSet" o = NM.Setting.SettingOptionSetMethodInfo
    ResolveSettingBluetoothMethod "optionSetBoolean" o = NM.Setting.SettingOptionSetBooleanMethodInfo
    ResolveSettingBluetoothMethod "optionSetUint32" o = NM.Setting.SettingOptionSetUint32MethodInfo
    ResolveSettingBluetoothMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSettingBluetoothMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSettingBluetoothMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSettingBluetoothMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSettingBluetoothMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSettingBluetoothMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSettingBluetoothMethod "toString" o = NM.Setting.SettingToStringMethodInfo
    ResolveSettingBluetoothMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSettingBluetoothMethod "verify" o = NM.Setting.SettingVerifyMethodInfo
    ResolveSettingBluetoothMethod "verifySecrets" o = NM.Setting.SettingVerifySecretsMethodInfo
    ResolveSettingBluetoothMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSettingBluetoothMethod "getBdaddr" o = SettingBluetoothGetBdaddrMethodInfo
    ResolveSettingBluetoothMethod "getConnectionType" o = SettingBluetoothGetConnectionTypeMethodInfo
    ResolveSettingBluetoothMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSettingBluetoothMethod "getDbusPropertyType" o = NM.Setting.SettingGetDbusPropertyTypeMethodInfo
    ResolveSettingBluetoothMethod "getName" o = NM.Setting.SettingGetNameMethodInfo
    ResolveSettingBluetoothMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSettingBluetoothMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSettingBluetoothMethod "getSecretFlags" o = NM.Setting.SettingGetSecretFlagsMethodInfo
    ResolveSettingBluetoothMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSettingBluetoothMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSettingBluetoothMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSettingBluetoothMethod "setSecretFlags" o = NM.Setting.SettingSetSecretFlagsMethodInfo
    ResolveSettingBluetoothMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

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

-- | Set the value of the “@bdaddr@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingBluetooth [ #bdaddr 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingBluetoothBdaddr :: (MonadIO m, IsSettingBluetooth o) => o -> T.Text -> m ()
setSettingBluetoothBdaddr :: forall (m :: * -> *) o.
(MonadIO m, IsSettingBluetooth o) =>
o -> Text -> m ()
setSettingBluetoothBdaddr o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
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
"bdaddr" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

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

-- | Set the value of the “@bdaddr@” 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' #bdaddr
-- @
clearSettingBluetoothBdaddr :: (MonadIO m, IsSettingBluetooth o) => o -> m ()
clearSettingBluetoothBdaddr :: forall (m :: * -> *) o.
(MonadIO m, IsSettingBluetooth o) =>
o -> m ()
clearSettingBluetoothBdaddr o
obj = 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
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"bdaddr" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingBluetoothBdaddrPropertyInfo
instance AttrInfo SettingBluetoothBdaddrPropertyInfo where
    type AttrAllowedOps SettingBluetoothBdaddrPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingBluetoothBdaddrPropertyInfo = IsSettingBluetooth
    type AttrSetTypeConstraint SettingBluetoothBdaddrPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingBluetoothBdaddrPropertyInfo = (~) T.Text
    type AttrTransferType SettingBluetoothBdaddrPropertyInfo = T.Text
    type AttrGetType SettingBluetoothBdaddrPropertyInfo = T.Text
    type AttrLabel SettingBluetoothBdaddrPropertyInfo = "bdaddr"
    type AttrOrigin SettingBluetoothBdaddrPropertyInfo = SettingBluetooth
    attrGet = getSettingBluetoothBdaddr
    attrSet = setSettingBluetoothBdaddr
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingBluetoothBdaddr
    attrClear = clearSettingBluetoothBdaddr
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingBluetooth.bdaddr"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingBluetooth.html#g:attr:bdaddr"
        })
#endif

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

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

-- | Set the value of the “@type@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settingBluetooth [ #type 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingBluetoothType :: (MonadIO m, IsSettingBluetooth o) => o -> T.Text -> m ()
setSettingBluetoothType :: forall (m :: * -> *) o.
(MonadIO m, IsSettingBluetooth o) =>
o -> Text -> m ()
setSettingBluetoothType o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
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
"type" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

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

-- | Set the value of the “@type@” 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' #type
-- @
clearSettingBluetoothType :: (MonadIO m, IsSettingBluetooth o) => o -> m ()
clearSettingBluetoothType :: forall (m :: * -> *) o.
(MonadIO m, IsSettingBluetooth o) =>
o -> m ()
clearSettingBluetoothType o
obj = 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
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"type" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingBluetoothTypePropertyInfo
instance AttrInfo SettingBluetoothTypePropertyInfo where
    type AttrAllowedOps SettingBluetoothTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingBluetoothTypePropertyInfo = IsSettingBluetooth
    type AttrSetTypeConstraint SettingBluetoothTypePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingBluetoothTypePropertyInfo = (~) T.Text
    type AttrTransferType SettingBluetoothTypePropertyInfo = T.Text
    type AttrGetType SettingBluetoothTypePropertyInfo = (Maybe T.Text)
    type AttrLabel SettingBluetoothTypePropertyInfo = "type"
    type AttrOrigin SettingBluetoothTypePropertyInfo = SettingBluetooth
    attrGet = getSettingBluetoothType
    attrSet = setSettingBluetoothType
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingBluetoothType
    attrClear = clearSettingBluetoothType
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingBluetooth.type"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingBluetooth.html#g:attr:type"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SettingBluetooth
type instance O.AttributeList SettingBluetooth = SettingBluetoothAttributeList
type SettingBluetoothAttributeList = ('[ '("bdaddr", SettingBluetoothBdaddrPropertyInfo), '("name", NM.Setting.SettingNamePropertyInfo), '("type", SettingBluetoothTypePropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
settingBluetoothBdaddr :: AttrLabelProxy "bdaddr"
settingBluetoothBdaddr = AttrLabelProxy

settingBluetoothType :: AttrLabelProxy "type"
settingBluetoothType = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SettingBluetooth = SettingBluetoothSignalList
type SettingBluetoothSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method SettingBluetooth::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "NM" , name = "SettingBluetooth" })
-- throws : False
-- Skip return : False

foreign import ccall "nm_setting_bluetooth_new" nm_setting_bluetooth_new :: 
    IO (Ptr SettingBluetooth)

-- | Creates a new t'GI.NM.Objects.SettingBluetooth.SettingBluetooth' object with default values.
settingBluetoothNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m SettingBluetooth
    -- ^ __Returns:__ the new empty t'GI.NM.Objects.SettingBluetooth.SettingBluetooth' object
settingBluetoothNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m SettingBluetooth
settingBluetoothNew  = IO SettingBluetooth -> m SettingBluetooth
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SettingBluetooth -> m SettingBluetooth)
-> IO SettingBluetooth -> m SettingBluetooth
forall a b. (a -> b) -> a -> b
$ do
    Ptr SettingBluetooth
result <- IO (Ptr SettingBluetooth)
nm_setting_bluetooth_new
    Text -> Ptr SettingBluetooth -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingBluetoothNew" Ptr SettingBluetooth
result
    SettingBluetooth
result' <- ((ManagedPtr SettingBluetooth -> SettingBluetooth)
-> Ptr SettingBluetooth -> IO SettingBluetooth
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SettingBluetooth -> SettingBluetooth
SettingBluetooth) Ptr SettingBluetooth
result
    SettingBluetooth -> IO SettingBluetooth
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SettingBluetooth
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method SettingBluetooth::get_bdaddr
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingBluetooth" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingBluetooth"
--                 , 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_setting_bluetooth_get_bdaddr" nm_setting_bluetooth_get_bdaddr :: 
    Ptr SettingBluetooth ->                 -- setting : TInterface (Name {namespace = "NM", name = "SettingBluetooth"})
    IO CString

-- | Gets the Bluetooth address of the remote device which this setting
-- describes a connection to.
settingBluetoothGetBdaddr ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingBluetooth a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingBluetooth.SettingBluetooth'
    -> m T.Text
    -- ^ __Returns:__ the Bluetooth address
settingBluetoothGetBdaddr :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingBluetooth a) =>
a -> m Text
settingBluetoothGetBdaddr a
setting = 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 SettingBluetooth
setting' <- a -> IO (Ptr SettingBluetooth)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingBluetooth -> IO CString
nm_setting_bluetooth_get_bdaddr Ptr SettingBluetooth
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingBluetoothGetBdaddr" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SettingBluetoothGetBdaddrMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingBluetooth a) => O.OverloadedMethod SettingBluetoothGetBdaddrMethodInfo a signature where
    overloadedMethod = settingBluetoothGetBdaddr

instance O.OverloadedMethodInfo SettingBluetoothGetBdaddrMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingBluetooth.settingBluetoothGetBdaddr",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingBluetooth.html#v:settingBluetoothGetBdaddr"
        })


#endif

-- method SettingBluetooth::get_connection_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setting"
--           , argType =
--               TInterface Name { namespace = "NM" , name = "SettingBluetooth" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #NMSettingBluetooth"
--                 , 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_setting_bluetooth_get_connection_type" nm_setting_bluetooth_get_connection_type :: 
    Ptr SettingBluetooth ->                 -- setting : TInterface (Name {namespace = "NM", name = "SettingBluetooth"})
    IO CString

-- | Returns the connection method for communicating with the remote device (i.e.
-- either DUN to a DUN-capable device or PANU to a NAP-capable device).
settingBluetoothGetConnectionType ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettingBluetooth a) =>
    a
    -- ^ /@setting@/: the t'GI.NM.Objects.SettingBluetooth.SettingBluetooth'
    -> m T.Text
    -- ^ __Returns:__ the type, either 'GI.NM.Constants.SETTING_BLUETOOTH_TYPE_PANU',
    -- 'GI.NM.Constants.SETTING_BLUETOOTH_TYPE_NAP' or 'GI.NM.Constants.SETTING_BLUETOOTH_TYPE_DUN'
settingBluetoothGetConnectionType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingBluetooth a) =>
a -> m Text
settingBluetoothGetConnectionType a
setting = 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 SettingBluetooth
setting' <- a -> IO (Ptr SettingBluetooth)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setting
    CString
result <- Ptr SettingBluetooth -> IO CString
nm_setting_bluetooth_get_connection_type Ptr SettingBluetooth
setting'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingBluetoothGetConnectionType" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setting
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SettingBluetoothGetConnectionTypeMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSettingBluetooth a) => O.OverloadedMethod SettingBluetoothGetConnectionTypeMethodInfo a signature where
    overloadedMethod = settingBluetoothGetConnectionType

instance O.OverloadedMethodInfo SettingBluetoothGetConnectionTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.NM.Objects.SettingBluetooth.settingBluetoothGetConnectionType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-nm-1.0.1/docs/GI-NM-Objects-SettingBluetooth.html#v:settingBluetoothGetConnectionType"
        })


#endif