{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GDebugController@ is an interface to expose control of debugging features and
-- debug output.
-- 
-- It is implemented on Linux using t'GI.Gio.Objects.DebugControllerDBus.DebugControllerDBus', which
-- exposes a D-Bus interface to allow authenticated peers to control debug
-- features in this process.
-- 
-- Whether debug output is enabled is exposed as
-- t'GI.Gio.Interfaces.DebugController.DebugController':@/debug-enabled/@. This controls
-- 'GI.GLib.Functions.logSetDebugEnabled' by default. Application code may
-- connect to the [Object::notify]("GI.GObject.Objects.Object#g:signal:notify") signal for it
-- to control other parts of its debug infrastructure as necessary.
-- 
-- If your application or service is using the default GLib log writer function,
-- creating one of the built-in implementations of @GDebugController@ should be
-- all that’s needed to dynamically enable or disable debug output.
-- 
-- /Since: 2.72/

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

module GI.Gio.Interfaces.DebugController
    ( 

-- * Exported types
    DebugController(..)                     ,
    IsDebugController                       ,
    toDebugController                       ,


 -- * 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"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [init]("GI.Gio.Interfaces.Initable#g:method:init"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [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"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDebugEnabled]("GI.Gio.Interfaces.DebugController#g:method:getDebugEnabled"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDebugEnabled]("GI.Gio.Interfaces.DebugController#g:method:setDebugEnabled"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveDebugControllerMethod            ,
#endif

-- ** getDebugEnabled #method:getDebugEnabled#

#if defined(ENABLE_OVERLOADING)
    DebugControllerGetDebugEnabledMethodInfo,
#endif
    debugControllerGetDebugEnabled          ,


-- ** setDebugEnabled #method:setDebugEnabled#

#if defined(ENABLE_OVERLOADING)
    DebugControllerSetDebugEnabledMethodInfo,
#endif
    debugControllerSetDebugEnabled          ,




 -- * Properties


-- ** debugEnabled #attr:debugEnabled#
-- | 'P.True' if debug output should be exposed (for example by forwarding it to
-- the journal), 'P.False' otherwise.
-- 
-- /Since: 2.72/

#if defined(ENABLE_OVERLOADING)
    DebugControllerDebugEnabledPropertyInfo ,
#endif
    constructDebugControllerDebugEnabled    ,
#if defined(ENABLE_OVERLOADING)
    debugControllerDebugEnabled             ,
#endif
    getDebugControllerDebugEnabled          ,
    setDebugControllerDebugEnabled          ,




    ) 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.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.PollFD as GLib.PollFD
import qualified GI.GLib.Structs.Source as GLib.Source
import qualified GI.GObject.Callbacks as GObject.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.GObject.Structs.Parameter as GObject.Parameter
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Initable as Gio.Initable
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable

#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Initable as Gio.Initable

#endif

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

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

foreign import ccall "g_debug_controller_get_type"
    c_g_debug_controller_get_type :: IO B.Types.GType

instance B.Types.TypedObject DebugController where
    glibType :: IO GType
glibType = IO GType
c_g_debug_controller_get_type

instance B.Types.GObject DebugController

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

instance O.HasParentTypes DebugController
type instance O.ParentTypes DebugController = '[Gio.Initable.Initable, GObject.Object.Object]

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

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

-- VVV Prop "debug-enabled"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@debug-enabled@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' debugController #debugEnabled
-- @
getDebugControllerDebugEnabled :: (MonadIO m, IsDebugController o) => o -> m Bool
getDebugControllerDebugEnabled :: forall (m :: * -> *) o.
(MonadIO m, IsDebugController o) =>
o -> m Bool
getDebugControllerDebugEnabled o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"debug-enabled"

-- | Set the value of the “@debug-enabled@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' debugController [ #debugEnabled 'Data.GI.Base.Attributes.:=' value ]
-- @
setDebugControllerDebugEnabled :: (MonadIO m, IsDebugController o) => o -> Bool -> m ()
setDebugControllerDebugEnabled :: forall (m :: * -> *) o.
(MonadIO m, IsDebugController o) =>
o -> Bool -> m ()
setDebugControllerDebugEnabled o
obj Bool
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"debug-enabled" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@debug-enabled@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDebugControllerDebugEnabled :: (IsDebugController o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructDebugControllerDebugEnabled :: forall o (m :: * -> *).
(IsDebugController o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructDebugControllerDebugEnabled Bool
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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"debug-enabled" Bool
val

#if defined(ENABLE_OVERLOADING)
data DebugControllerDebugEnabledPropertyInfo
instance AttrInfo DebugControllerDebugEnabledPropertyInfo where
    type AttrAllowedOps DebugControllerDebugEnabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DebugControllerDebugEnabledPropertyInfo = IsDebugController
    type AttrSetTypeConstraint DebugControllerDebugEnabledPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint DebugControllerDebugEnabledPropertyInfo = (~) Bool
    type AttrTransferType DebugControllerDebugEnabledPropertyInfo = Bool
    type AttrGetType DebugControllerDebugEnabledPropertyInfo = Bool
    type AttrLabel DebugControllerDebugEnabledPropertyInfo = "debug-enabled"
    type AttrOrigin DebugControllerDebugEnabledPropertyInfo = DebugController
    attrGet = getDebugControllerDebugEnabled
    attrSet = setDebugControllerDebugEnabled
    attrTransfer _ v = do
        return v
    attrConstruct = constructDebugControllerDebugEnabled
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DebugController.debugEnabled"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-DebugController.html#g:attr:debugEnabled"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DebugController
type instance O.AttributeList DebugController = DebugControllerAttributeList
type DebugControllerAttributeList = ('[ '("debugEnabled", DebugControllerDebugEnabledPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
debugControllerDebugEnabled :: AttrLabelProxy "debugEnabled"
debugControllerDebugEnabled = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveDebugControllerMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveDebugControllerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDebugControllerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDebugControllerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDebugControllerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDebugControllerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDebugControllerMethod "init" o = Gio.Initable.InitableInitMethodInfo
    ResolveDebugControllerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDebugControllerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDebugControllerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDebugControllerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDebugControllerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDebugControllerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDebugControllerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDebugControllerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDebugControllerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDebugControllerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDebugControllerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDebugControllerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDebugControllerMethod "getDebugEnabled" o = DebugControllerGetDebugEnabledMethodInfo
    ResolveDebugControllerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDebugControllerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDebugControllerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDebugControllerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDebugControllerMethod "setDebugEnabled" o = DebugControllerSetDebugEnabledMethodInfo
    ResolveDebugControllerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDebugControllerMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- method DebugController::get_debug_enabled
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DebugController" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDebugController"
--                 , 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 "g_debug_controller_get_debug_enabled" g_debug_controller_get_debug_enabled :: 
    Ptr DebugController ->                  -- self : TInterface (Name {namespace = "Gio", name = "DebugController"})
    IO CInt

-- | Get the value of t'GI.Gio.Interfaces.DebugController.DebugController':@/debug-enabled/@.
-- 
-- /Since: 2.72/
debugControllerGetDebugEnabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsDebugController a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Interfaces.DebugController.DebugController'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if debug output should be exposed, 'P.False' otherwise
debugControllerGetDebugEnabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDebugController a) =>
a -> m Bool
debugControllerGetDebugEnabled a
self = 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 DebugController
self' <- a -> IO (Ptr DebugController)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr DebugController -> IO CInt
g_debug_controller_get_debug_enabled Ptr DebugController
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DebugControllerGetDebugEnabledMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDebugController a) => O.OverloadedMethod DebugControllerGetDebugEnabledMethodInfo a signature where
    overloadedMethod = debugControllerGetDebugEnabled

instance O.OverloadedMethodInfo DebugControllerGetDebugEnabledMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DebugController.debugControllerGetDebugEnabled",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-DebugController.html#v:debugControllerGetDebugEnabled"
        })


#endif

-- method DebugController::set_debug_enabled
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DebugController" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDebugController"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "debug_enabled"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "%TRUE if debug output should be exposed, %FALSE otherwise"
--                 , 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 "g_debug_controller_set_debug_enabled" g_debug_controller_set_debug_enabled :: 
    Ptr DebugController ->                  -- self : TInterface (Name {namespace = "Gio", name = "DebugController"})
    CInt ->                                 -- debug_enabled : TBasicType TBoolean
    IO ()

-- | Set the value of t'GI.Gio.Interfaces.DebugController.DebugController':@/debug-enabled/@.
-- 
-- /Since: 2.72/
debugControllerSetDebugEnabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsDebugController a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Interfaces.DebugController.DebugController'
    -> Bool
    -- ^ /@debugEnabled@/: 'P.True' if debug output should be exposed, 'P.False' otherwise
    -> m ()
debugControllerSetDebugEnabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDebugController a) =>
a -> Bool -> m ()
debugControllerSetDebugEnabled a
self Bool
debugEnabled = 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 DebugController
self' <- a -> IO (Ptr DebugController)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let debugEnabled' :: CInt
debugEnabled' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
debugEnabled
    Ptr DebugController -> CInt -> IO ()
g_debug_controller_set_debug_enabled Ptr DebugController
self' CInt
debugEnabled'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DebugControllerSetDebugEnabledMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsDebugController a) => O.OverloadedMethod DebugControllerSetDebugEnabledMethodInfo a signature where
    overloadedMethod = debugControllerSetDebugEnabled

instance O.OverloadedMethodInfo DebugControllerSetDebugEnabledMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.DebugController.debugControllerSetDebugEnabled",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-DebugController.html#v:debugControllerSetDebugEnabled"
        })


#endif

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

#endif