{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Native dialogs are platform dialogs that don\'t use @GtkDialog@.
-- 
-- They are used in order to integrate better with a platform, by
-- looking the same as other native applications and supporting
-- platform specific features.
-- 
-- The t'GI.Gtk.Objects.Dialog.Dialog' functions cannot be used on such objects,
-- but we need a similar API in order to drive them. The @GtkNativeDialog@
-- object is an API that allows you to do this. It allows you to set
-- various common properties on the dialog, as well as show and hide
-- it and get a [NativeDialog::response]("GI.Gtk.Objects.NativeDialog#g:signal:response") signal when the user
-- finished with the dialog.
-- 
-- Note that unlike @GtkDialog@, @GtkNativeDialog@ objects are not
-- toplevel widgets, and GTK does not keep them alive. It is your
-- responsibility to keep a reference until you are done with the
-- object.

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

module GI.Gtk.Objects.NativeDialog
    ( 

-- * Exported types
    NativeDialog(..)                        ,
    IsNativeDialog                          ,
    toNativeDialog                          ,


 -- * 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"), [destroy]("GI.Gtk.Objects.NativeDialog#g:method:destroy"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hide]("GI.Gtk.Objects.NativeDialog#g:method:hide"), [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"), [show]("GI.Gtk.Objects.NativeDialog#g:method:show"), [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"), [getModal]("GI.Gtk.Objects.NativeDialog#g:method:getModal"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getTitle]("GI.Gtk.Objects.NativeDialog#g:method:getTitle"), [getTransientFor]("GI.Gtk.Objects.NativeDialog#g:method:getTransientFor"), [getVisible]("GI.Gtk.Objects.NativeDialog#g:method:getVisible").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setModal]("GI.Gtk.Objects.NativeDialog#g:method:setModal"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setTitle]("GI.Gtk.Objects.NativeDialog#g:method:setTitle"), [setTransientFor]("GI.Gtk.Objects.NativeDialog#g:method:setTransientFor").

#if defined(ENABLE_OVERLOADING)
    ResolveNativeDialogMethod               ,
#endif

-- ** destroy #method:destroy#

#if defined(ENABLE_OVERLOADING)
    NativeDialogDestroyMethodInfo           ,
#endif
    nativeDialogDestroy                     ,


-- ** getModal #method:getModal#

#if defined(ENABLE_OVERLOADING)
    NativeDialogGetModalMethodInfo          ,
#endif
    nativeDialogGetModal                    ,


-- ** getTitle #method:getTitle#

#if defined(ENABLE_OVERLOADING)
    NativeDialogGetTitleMethodInfo          ,
#endif
    nativeDialogGetTitle                    ,


-- ** getTransientFor #method:getTransientFor#

#if defined(ENABLE_OVERLOADING)
    NativeDialogGetTransientForMethodInfo   ,
#endif
    nativeDialogGetTransientFor             ,


-- ** getVisible #method:getVisible#

#if defined(ENABLE_OVERLOADING)
    NativeDialogGetVisibleMethodInfo        ,
#endif
    nativeDialogGetVisible                  ,


-- ** hide #method:hide#

#if defined(ENABLE_OVERLOADING)
    NativeDialogHideMethodInfo              ,
#endif
    nativeDialogHide                        ,


-- ** setModal #method:setModal#

#if defined(ENABLE_OVERLOADING)
    NativeDialogSetModalMethodInfo          ,
#endif
    nativeDialogSetModal                    ,


-- ** setTitle #method:setTitle#

#if defined(ENABLE_OVERLOADING)
    NativeDialogSetTitleMethodInfo          ,
#endif
    nativeDialogSetTitle                    ,


-- ** setTransientFor #method:setTransientFor#

#if defined(ENABLE_OVERLOADING)
    NativeDialogSetTransientForMethodInfo   ,
#endif
    nativeDialogSetTransientFor             ,


-- ** show #method:show#

#if defined(ENABLE_OVERLOADING)
    NativeDialogShowMethodInfo              ,
#endif
    nativeDialogShow                        ,




 -- * Properties


-- ** modal #attr:modal#
-- | Whether the window should be modal with respect to its transient parent.

#if defined(ENABLE_OVERLOADING)
    NativeDialogModalPropertyInfo           ,
#endif
    constructNativeDialogModal              ,
    getNativeDialogModal                    ,
#if defined(ENABLE_OVERLOADING)
    nativeDialogModal                       ,
#endif
    setNativeDialogModal                    ,


-- ** title #attr:title#
-- | The title of the dialog window

#if defined(ENABLE_OVERLOADING)
    NativeDialogTitlePropertyInfo           ,
#endif
    constructNativeDialogTitle              ,
    getNativeDialogTitle                    ,
#if defined(ENABLE_OVERLOADING)
    nativeDialogTitle                       ,
#endif
    setNativeDialogTitle                    ,


-- ** transientFor #attr:transientFor#
-- | The transient parent of the dialog, or 'P.Nothing' for none.

#if defined(ENABLE_OVERLOADING)
    NativeDialogTransientForPropertyInfo    ,
#endif
    clearNativeDialogTransientFor           ,
    constructNativeDialogTransientFor       ,
    getNativeDialogTransientFor             ,
#if defined(ENABLE_OVERLOADING)
    nativeDialogTransientFor                ,
#endif
    setNativeDialogTransientFor             ,


-- ** visible #attr:visible#
-- | Whether the window is currently visible.

#if defined(ENABLE_OVERLOADING)
    NativeDialogVisiblePropertyInfo         ,
#endif
    constructNativeDialogVisible            ,
    getNativeDialogVisible                  ,
#if defined(ENABLE_OVERLOADING)
    nativeDialogVisible                     ,
#endif
    setNativeDialogVisible                  ,




 -- * Signals


-- ** response #signal:response#

    NativeDialogResponseCallback            ,
#if defined(ENABLE_OVERLOADING)
    NativeDialogResponseSignalInfo          ,
#endif
    afterNativeDialogResponse               ,
    onNativeDialogResponse                  ,




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

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

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

foreign import ccall "gtk_native_dialog_get_type"
    c_gtk_native_dialog_get_type :: IO B.Types.GType

instance B.Types.TypedObject NativeDialog where
    glibType :: IO GType
glibType = IO GType
c_gtk_native_dialog_get_type

instance B.Types.GObject NativeDialog

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

instance O.HasParentTypes NativeDialog
type instance O.ParentTypes NativeDialog = '[GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveNativeDialogMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveNativeDialogMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveNativeDialogMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveNativeDialogMethod "destroy" o = NativeDialogDestroyMethodInfo
    ResolveNativeDialogMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveNativeDialogMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveNativeDialogMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveNativeDialogMethod "hide" o = NativeDialogHideMethodInfo
    ResolveNativeDialogMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveNativeDialogMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveNativeDialogMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveNativeDialogMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveNativeDialogMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveNativeDialogMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveNativeDialogMethod "show" o = NativeDialogShowMethodInfo
    ResolveNativeDialogMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveNativeDialogMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveNativeDialogMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveNativeDialogMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveNativeDialogMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveNativeDialogMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveNativeDialogMethod "getModal" o = NativeDialogGetModalMethodInfo
    ResolveNativeDialogMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveNativeDialogMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveNativeDialogMethod "getTitle" o = NativeDialogGetTitleMethodInfo
    ResolveNativeDialogMethod "getTransientFor" o = NativeDialogGetTransientForMethodInfo
    ResolveNativeDialogMethod "getVisible" o = NativeDialogGetVisibleMethodInfo
    ResolveNativeDialogMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveNativeDialogMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveNativeDialogMethod "setModal" o = NativeDialogSetModalMethodInfo
    ResolveNativeDialogMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveNativeDialogMethod "setTitle" o = NativeDialogSetTitleMethodInfo
    ResolveNativeDialogMethod "setTransientFor" o = NativeDialogSetTransientForMethodInfo
    ResolveNativeDialogMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- signal NativeDialog::response
-- | Emitted when the user responds to the dialog.
-- 
-- When this is called the dialog has been hidden.
-- 
-- If you call 'GI.Gtk.Objects.NativeDialog.nativeDialogHide' before the user
-- responds to the dialog this signal will not be emitted.
type NativeDialogResponseCallback =
    Int32
    -- ^ /@responseId@/: the response ID
    -> IO ()

type C_NativeDialogResponseCallback =
    Ptr NativeDialog ->                     -- object
    Int32 ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_NativeDialogResponseCallback :: 
    GObject a => (a -> NativeDialogResponseCallback) ->
    C_NativeDialogResponseCallback
wrap_NativeDialogResponseCallback :: forall a.
GObject a =>
(a -> NativeDialogResponseCallback)
-> C_NativeDialogResponseCallback
wrap_NativeDialogResponseCallback a -> NativeDialogResponseCallback
gi'cb Ptr NativeDialog
gi'selfPtr Int32
responseId Ptr ()
_ = do
    Ptr NativeDialog -> (NativeDialog -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr NativeDialog
gi'selfPtr ((NativeDialog -> IO ()) -> IO ())
-> (NativeDialog -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \NativeDialog
gi'self -> a -> NativeDialogResponseCallback
gi'cb (NativeDialog -> a
forall a b. Coercible a b => a -> b
Coerce.coerce NativeDialog
gi'self)  Int32
responseId


-- | Connect a signal handler for the [response](#signal:response) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' nativeDialog #response callback
-- @
-- 
-- 
onNativeDialogResponse :: (IsNativeDialog a, MonadIO m) => a -> ((?self :: a) => NativeDialogResponseCallback) -> m SignalHandlerId
onNativeDialogResponse :: forall a (m :: * -> *).
(IsNativeDialog a, MonadIO m) =>
a
-> ((?self::a) => NativeDialogResponseCallback)
-> m SignalHandlerId
onNativeDialogResponse a
obj (?self::a) => NativeDialogResponseCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> NativeDialogResponseCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => NativeDialogResponseCallback
NativeDialogResponseCallback
cb
    let wrapped' :: C_NativeDialogResponseCallback
wrapped' = (a -> NativeDialogResponseCallback)
-> C_NativeDialogResponseCallback
forall a.
GObject a =>
(a -> NativeDialogResponseCallback)
-> C_NativeDialogResponseCallback
wrap_NativeDialogResponseCallback a -> NativeDialogResponseCallback
wrapped
    FunPtr C_NativeDialogResponseCallback
wrapped'' <- C_NativeDialogResponseCallback
-> IO (FunPtr C_NativeDialogResponseCallback)
mk_NativeDialogResponseCallback C_NativeDialogResponseCallback
wrapped'
    a
-> Text
-> FunPtr C_NativeDialogResponseCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"response" FunPtr C_NativeDialogResponseCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [response](#signal:response) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' nativeDialog #response callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterNativeDialogResponse :: (IsNativeDialog a, MonadIO m) => a -> ((?self :: a) => NativeDialogResponseCallback) -> m SignalHandlerId
afterNativeDialogResponse :: forall a (m :: * -> *).
(IsNativeDialog a, MonadIO m) =>
a
-> ((?self::a) => NativeDialogResponseCallback)
-> m SignalHandlerId
afterNativeDialogResponse a
obj (?self::a) => NativeDialogResponseCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> NativeDialogResponseCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => NativeDialogResponseCallback
NativeDialogResponseCallback
cb
    let wrapped' :: C_NativeDialogResponseCallback
wrapped' = (a -> NativeDialogResponseCallback)
-> C_NativeDialogResponseCallback
forall a.
GObject a =>
(a -> NativeDialogResponseCallback)
-> C_NativeDialogResponseCallback
wrap_NativeDialogResponseCallback a -> NativeDialogResponseCallback
wrapped
    FunPtr C_NativeDialogResponseCallback
wrapped'' <- C_NativeDialogResponseCallback
-> IO (FunPtr C_NativeDialogResponseCallback)
mk_NativeDialogResponseCallback C_NativeDialogResponseCallback
wrapped'
    a
-> Text
-> FunPtr C_NativeDialogResponseCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"response" FunPtr C_NativeDialogResponseCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data NativeDialogResponseSignalInfo
instance SignalInfo NativeDialogResponseSignalInfo where
    type HaskellCallbackType NativeDialogResponseSignalInfo = NativeDialogResponseCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_NativeDialogResponseCallback cb
        cb'' <- mk_NativeDialogResponseCallback cb'
        connectSignalFunPtr obj "response" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.NativeDialog::response"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-NativeDialog.html#g:signal:response"})

#endif

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

-- | Get the value of the “@modal@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' nativeDialog #modal
-- @
getNativeDialogModal :: (MonadIO m, IsNativeDialog o) => o -> m Bool
getNativeDialogModal :: forall (m :: * -> *) o.
(MonadIO m, IsNativeDialog o) =>
o -> m Bool
getNativeDialogModal 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
"modal"

-- | Set the value of the “@modal@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' nativeDialog [ #modal 'Data.GI.Base.Attributes.:=' value ]
-- @
setNativeDialogModal :: (MonadIO m, IsNativeDialog o) => o -> Bool -> m ()
setNativeDialogModal :: forall (m :: * -> *) o.
(MonadIO m, IsNativeDialog o) =>
o -> Bool -> m ()
setNativeDialogModal 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
"modal" Bool
val

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

#if defined(ENABLE_OVERLOADING)
data NativeDialogModalPropertyInfo
instance AttrInfo NativeDialogModalPropertyInfo where
    type AttrAllowedOps NativeDialogModalPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint NativeDialogModalPropertyInfo = IsNativeDialog
    type AttrSetTypeConstraint NativeDialogModalPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint NativeDialogModalPropertyInfo = (~) Bool
    type AttrTransferType NativeDialogModalPropertyInfo = Bool
    type AttrGetType NativeDialogModalPropertyInfo = Bool
    type AttrLabel NativeDialogModalPropertyInfo = "modal"
    type AttrOrigin NativeDialogModalPropertyInfo = NativeDialog
    attrGet = getNativeDialogModal
    attrSet = setNativeDialogModal
    attrTransfer _ v = do
        return v
    attrConstruct = constructNativeDialogModal
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.NativeDialog.modal"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-NativeDialog.html#g:attr:modal"
        })
#endif

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data NativeDialogTitlePropertyInfo
instance AttrInfo NativeDialogTitlePropertyInfo where
    type AttrAllowedOps NativeDialogTitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint NativeDialogTitlePropertyInfo = IsNativeDialog
    type AttrSetTypeConstraint NativeDialogTitlePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint NativeDialogTitlePropertyInfo = (~) T.Text
    type AttrTransferType NativeDialogTitlePropertyInfo = T.Text
    type AttrGetType NativeDialogTitlePropertyInfo = (Maybe T.Text)
    type AttrLabel NativeDialogTitlePropertyInfo = "title"
    type AttrOrigin NativeDialogTitlePropertyInfo = NativeDialog
    attrGet = getNativeDialogTitle
    attrSet = setNativeDialogTitle
    attrTransfer _ v = do
        return v
    attrConstruct = constructNativeDialogTitle
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.NativeDialog.title"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-NativeDialog.html#g:attr:title"
        })
#endif

-- VVV Prop "transient-for"
   -- Type: TInterface (Name {namespace = "Gtk", name = "Window"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@transient-for@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' nativeDialog #transientFor
-- @
getNativeDialogTransientFor :: (MonadIO m, IsNativeDialog o) => o -> m (Maybe Gtk.Window.Window)
getNativeDialogTransientFor :: forall (m :: * -> *) o.
(MonadIO m, IsNativeDialog o) =>
o -> m (Maybe Window)
getNativeDialogTransientFor o
obj = IO (Maybe Window) -> m (Maybe Window)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Window) -> m (Maybe Window))
-> IO (Maybe Window) -> m (Maybe Window)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Window -> Window) -> IO (Maybe Window)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"transient-for" ManagedPtr Window -> Window
Gtk.Window.Window

-- | Set the value of the “@transient-for@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' nativeDialog [ #transientFor 'Data.GI.Base.Attributes.:=' value ]
-- @
setNativeDialogTransientFor :: (MonadIO m, IsNativeDialog o, Gtk.Window.IsWindow a) => o -> a -> m ()
setNativeDialogTransientFor :: forall (m :: * -> *) o a.
(MonadIO m, IsNativeDialog o, IsWindow a) =>
o -> a -> m ()
setNativeDialogTransientFor o
obj a
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 a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"transient-for" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@transient-for@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructNativeDialogTransientFor :: (IsNativeDialog o, MIO.MonadIO m, Gtk.Window.IsWindow a) => a -> m (GValueConstruct o)
constructNativeDialogTransientFor :: forall o (m :: * -> *) a.
(IsNativeDialog o, MonadIO m, IsWindow a) =>
a -> m (GValueConstruct o)
constructNativeDialogTransientFor a
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 a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"transient-for" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@transient-for@” 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' #transientFor
-- @
clearNativeDialogTransientFor :: (MonadIO m, IsNativeDialog o) => o -> m ()
clearNativeDialogTransientFor :: forall (m :: * -> *) o. (MonadIO m, IsNativeDialog o) => o -> m ()
clearNativeDialogTransientFor 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 Window -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"transient-for" (Maybe Window
forall a. Maybe a
Nothing :: Maybe Gtk.Window.Window)

#if defined(ENABLE_OVERLOADING)
data NativeDialogTransientForPropertyInfo
instance AttrInfo NativeDialogTransientForPropertyInfo where
    type AttrAllowedOps NativeDialogTransientForPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint NativeDialogTransientForPropertyInfo = IsNativeDialog
    type AttrSetTypeConstraint NativeDialogTransientForPropertyInfo = Gtk.Window.IsWindow
    type AttrTransferTypeConstraint NativeDialogTransientForPropertyInfo = Gtk.Window.IsWindow
    type AttrTransferType NativeDialogTransientForPropertyInfo = Gtk.Window.Window
    type AttrGetType NativeDialogTransientForPropertyInfo = (Maybe Gtk.Window.Window)
    type AttrLabel NativeDialogTransientForPropertyInfo = "transient-for"
    type AttrOrigin NativeDialogTransientForPropertyInfo = NativeDialog
    attrGet = getNativeDialogTransientFor
    attrSet = setNativeDialogTransientFor
    attrTransfer _ v = do
        unsafeCastTo Gtk.Window.Window v
    attrConstruct = constructNativeDialogTransientFor
    attrClear = clearNativeDialogTransientFor
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.NativeDialog.transientFor"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-NativeDialog.html#g:attr:transientFor"
        })
#endif

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

-- | Get the value of the “@visible@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' nativeDialog #visible
-- @
getNativeDialogVisible :: (MonadIO m, IsNativeDialog o) => o -> m Bool
getNativeDialogVisible :: forall (m :: * -> *) o.
(MonadIO m, IsNativeDialog o) =>
o -> m Bool
getNativeDialogVisible 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
"visible"

-- | Set the value of the “@visible@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' nativeDialog [ #visible 'Data.GI.Base.Attributes.:=' value ]
-- @
setNativeDialogVisible :: (MonadIO m, IsNativeDialog o) => o -> Bool -> m ()
setNativeDialogVisible :: forall (m :: * -> *) o.
(MonadIO m, IsNativeDialog o) =>
o -> Bool -> m ()
setNativeDialogVisible 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
"visible" Bool
val

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

#if defined(ENABLE_OVERLOADING)
data NativeDialogVisiblePropertyInfo
instance AttrInfo NativeDialogVisiblePropertyInfo where
    type AttrAllowedOps NativeDialogVisiblePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint NativeDialogVisiblePropertyInfo = IsNativeDialog
    type AttrSetTypeConstraint NativeDialogVisiblePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint NativeDialogVisiblePropertyInfo = (~) Bool
    type AttrTransferType NativeDialogVisiblePropertyInfo = Bool
    type AttrGetType NativeDialogVisiblePropertyInfo = Bool
    type AttrLabel NativeDialogVisiblePropertyInfo = "visible"
    type AttrOrigin NativeDialogVisiblePropertyInfo = NativeDialog
    attrGet = getNativeDialogVisible
    attrSet = setNativeDialogVisible
    attrTransfer _ v = do
        return v
    attrConstruct = constructNativeDialogVisible
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.NativeDialog.visible"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-NativeDialog.html#g:attr:visible"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList NativeDialog
type instance O.AttributeList NativeDialog = NativeDialogAttributeList
type NativeDialogAttributeList = ('[ '("modal", NativeDialogModalPropertyInfo), '("title", NativeDialogTitlePropertyInfo), '("transientFor", NativeDialogTransientForPropertyInfo), '("visible", NativeDialogVisiblePropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
nativeDialogModal :: AttrLabelProxy "modal"
nativeDialogModal = AttrLabelProxy

nativeDialogTitle :: AttrLabelProxy "title"
nativeDialogTitle = AttrLabelProxy

nativeDialogTransientFor :: AttrLabelProxy "transientFor"
nativeDialogTransientFor = AttrLabelProxy

nativeDialogVisible :: AttrLabelProxy "visible"
nativeDialogVisible = AttrLabelProxy

#endif

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

#endif

-- method NativeDialog::destroy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "NativeDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkNativeDialog`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_native_dialog_destroy" gtk_native_dialog_destroy :: 
    Ptr NativeDialog ->                     -- self : TInterface (Name {namespace = "Gtk", name = "NativeDialog"})
    IO ()

-- | Destroys a dialog.
-- 
-- When a dialog is destroyed, it will break any references it holds
-- to other objects.
-- 
-- If it is visible it will be hidden and any underlying window system
-- resources will be destroyed.
-- 
-- Note that this does not release any reference to the object (as opposed
-- to destroying a @GtkWindow@) because there is no reference from the
-- windowing system to the @GtkNativeDialog@.
nativeDialogDestroy ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a @GtkNativeDialog@
    -> m ()
nativeDialogDestroy :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNativeDialog a) =>
a -> m ()
nativeDialogDestroy a
self = 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 NativeDialog
self' <- a -> IO (Ptr NativeDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr NativeDialog -> IO ()
gtk_native_dialog_destroy Ptr NativeDialog
self'
    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 NativeDialogDestroyMethodInfo
instance (signature ~ (m ()), MonadIO m, IsNativeDialog a) => O.OverloadedMethod NativeDialogDestroyMethodInfo a signature where
    overloadedMethod = nativeDialogDestroy

instance O.OverloadedMethodInfo NativeDialogDestroyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.NativeDialog.nativeDialogDestroy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-NativeDialog.html#v:nativeDialogDestroy"
        })


#endif

-- method NativeDialog::get_modal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "NativeDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkNativeDialog`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_native_dialog_get_modal" gtk_native_dialog_get_modal :: 
    Ptr NativeDialog ->                     -- self : TInterface (Name {namespace = "Gtk", name = "NativeDialog"})
    IO CInt

-- | Returns whether the dialog is modal.
nativeDialogGetModal ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a @GtkNativeDialog@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the dialog is set to be modal
nativeDialogGetModal :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNativeDialog a) =>
a -> m Bool
nativeDialogGetModal 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 NativeDialog
self' <- a -> IO (Ptr NativeDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr NativeDialog -> IO CInt
gtk_native_dialog_get_modal Ptr NativeDialog
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 NativeDialogGetModalMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsNativeDialog a) => O.OverloadedMethod NativeDialogGetModalMethodInfo a signature where
    overloadedMethod = nativeDialogGetModal

instance O.OverloadedMethodInfo NativeDialogGetModalMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.NativeDialog.nativeDialogGetModal",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-NativeDialog.html#v:nativeDialogGetModal"
        })


#endif

-- method NativeDialog::get_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "NativeDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkNativeDialog`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_native_dialog_get_title" gtk_native_dialog_get_title :: 
    Ptr NativeDialog ->                     -- self : TInterface (Name {namespace = "Gtk", name = "NativeDialog"})
    IO CString

-- | Gets the title of the @GtkNativeDialog@.
nativeDialogGetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a @GtkNativeDialog@
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the title of the dialog, or 'P.Nothing' if none has
    --    been set explicitly. The returned string is owned by the widget
    --    and must not be modified or freed.
nativeDialogGetTitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNativeDialog a) =>
a -> m (Maybe Text)
nativeDialogGetTitle a
self = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr NativeDialog
self' <- a -> IO (Ptr NativeDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr NativeDialog -> IO CString
gtk_native_dialog_get_title Ptr NativeDialog
self'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data NativeDialogGetTitleMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsNativeDialog a) => O.OverloadedMethod NativeDialogGetTitleMethodInfo a signature where
    overloadedMethod = nativeDialogGetTitle

instance O.OverloadedMethodInfo NativeDialogGetTitleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.NativeDialog.nativeDialogGetTitle",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-NativeDialog.html#v:nativeDialogGetTitle"
        })


#endif

-- method NativeDialog::get_transient_for
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "NativeDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkNativeDialog`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Window" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_native_dialog_get_transient_for" gtk_native_dialog_get_transient_for :: 
    Ptr NativeDialog ->                     -- self : TInterface (Name {namespace = "Gtk", name = "NativeDialog"})
    IO (Ptr Gtk.Window.Window)

-- | Fetches the transient parent for this window.
nativeDialogGetTransientFor ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a @GtkNativeDialog@
    -> m (Maybe Gtk.Window.Window)
    -- ^ __Returns:__ the transient parent for this window,
    --   or 'P.Nothing' if no transient parent has been set.
nativeDialogGetTransientFor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNativeDialog a) =>
a -> m (Maybe Window)
nativeDialogGetTransientFor a
self = IO (Maybe Window) -> m (Maybe Window)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Window) -> m (Maybe Window))
-> IO (Maybe Window) -> m (Maybe Window)
forall a b. (a -> b) -> a -> b
$ do
    Ptr NativeDialog
self' <- a -> IO (Ptr NativeDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Window
result <- Ptr NativeDialog -> IO (Ptr Window)
gtk_native_dialog_get_transient_for Ptr NativeDialog
self'
    Maybe Window
maybeResult <- Ptr Window -> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Window
result ((Ptr Window -> IO Window) -> IO (Maybe Window))
-> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \Ptr Window
result' -> do
        Window
result'' <- ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gtk.Window.Window) Ptr Window
result'
        Window -> IO Window
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Window
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Window -> IO (Maybe Window)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Window
maybeResult

#if defined(ENABLE_OVERLOADING)
data NativeDialogGetTransientForMethodInfo
instance (signature ~ (m (Maybe Gtk.Window.Window)), MonadIO m, IsNativeDialog a) => O.OverloadedMethod NativeDialogGetTransientForMethodInfo a signature where
    overloadedMethod = nativeDialogGetTransientFor

instance O.OverloadedMethodInfo NativeDialogGetTransientForMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.NativeDialog.nativeDialogGetTransientFor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-NativeDialog.html#v:nativeDialogGetTransientFor"
        })


#endif

-- method NativeDialog::get_visible
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "NativeDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkNativeDialog`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_native_dialog_get_visible" gtk_native_dialog_get_visible :: 
    Ptr NativeDialog ->                     -- self : TInterface (Name {namespace = "Gtk", name = "NativeDialog"})
    IO CInt

-- | Determines whether the dialog is visible.
nativeDialogGetVisible ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a @GtkNativeDialog@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the dialog is visible
nativeDialogGetVisible :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNativeDialog a) =>
a -> m Bool
nativeDialogGetVisible 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 NativeDialog
self' <- a -> IO (Ptr NativeDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr NativeDialog -> IO CInt
gtk_native_dialog_get_visible Ptr NativeDialog
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 NativeDialogGetVisibleMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsNativeDialog a) => O.OverloadedMethod NativeDialogGetVisibleMethodInfo a signature where
    overloadedMethod = nativeDialogGetVisible

instance O.OverloadedMethodInfo NativeDialogGetVisibleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.NativeDialog.nativeDialogGetVisible",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-NativeDialog.html#v:nativeDialogGetVisible"
        })


#endif

-- method NativeDialog::hide
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "NativeDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkNativeDialog`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_native_dialog_hide" gtk_native_dialog_hide :: 
    Ptr NativeDialog ->                     -- self : TInterface (Name {namespace = "Gtk", name = "NativeDialog"})
    IO ()

-- | Hides the dialog if it is visible, aborting any interaction.
-- 
-- Once this is called the [NativeDialog::response]("GI.Gtk.Objects.NativeDialog#g:signal:response") signal
-- will *not* be emitted until after the next call to
-- 'GI.Gtk.Objects.NativeDialog.nativeDialogShow'.
-- 
-- If the dialog is not visible this does nothing.
nativeDialogHide ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a @GtkNativeDialog@
    -> m ()
nativeDialogHide :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNativeDialog a) =>
a -> m ()
nativeDialogHide a
self = 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 NativeDialog
self' <- a -> IO (Ptr NativeDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr NativeDialog -> IO ()
gtk_native_dialog_hide Ptr NativeDialog
self'
    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 NativeDialogHideMethodInfo
instance (signature ~ (m ()), MonadIO m, IsNativeDialog a) => O.OverloadedMethod NativeDialogHideMethodInfo a signature where
    overloadedMethod = nativeDialogHide

instance O.OverloadedMethodInfo NativeDialogHideMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.NativeDialog.nativeDialogHide",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-NativeDialog.html#v:nativeDialogHide"
        })


#endif

-- method NativeDialog::set_modal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "NativeDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkNativeDialog`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "modal"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether the window is modal"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_native_dialog_set_modal" gtk_native_dialog_set_modal :: 
    Ptr NativeDialog ->                     -- self : TInterface (Name {namespace = "Gtk", name = "NativeDialog"})
    CInt ->                                 -- modal : TBasicType TBoolean
    IO ()

-- | Sets a dialog modal or non-modal.
-- 
-- Modal dialogs prevent interaction with other windows in the same
-- application. To keep modal dialogs on top of main application
-- windows, use 'GI.Gtk.Objects.NativeDialog.nativeDialogSetTransientFor' to make
-- the dialog transient for the parent; most window managers will
-- then disallow lowering the dialog below the parent.
nativeDialogSetModal ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a @GtkNativeDialog@
    -> Bool
    -- ^ /@modal@/: whether the window is modal
    -> m ()
nativeDialogSetModal :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNativeDialog a) =>
a -> Bool -> m ()
nativeDialogSetModal a
self Bool
modal = 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 NativeDialog
self' <- a -> IO (Ptr NativeDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let modal' :: CInt
modal' = (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
modal
    Ptr NativeDialog -> CInt -> IO ()
gtk_native_dialog_set_modal Ptr NativeDialog
self' CInt
modal'
    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 NativeDialogSetModalMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsNativeDialog a) => O.OverloadedMethod NativeDialogSetModalMethodInfo a signature where
    overloadedMethod = nativeDialogSetModal

instance O.OverloadedMethodInfo NativeDialogSetModalMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.NativeDialog.nativeDialogSetModal",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-NativeDialog.html#v:nativeDialogSetModal"
        })


#endif

-- method NativeDialog::set_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "NativeDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkNativeDialog`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "title"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "title of the dialog"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_native_dialog_set_title" gtk_native_dialog_set_title :: 
    Ptr NativeDialog ->                     -- self : TInterface (Name {namespace = "Gtk", name = "NativeDialog"})
    CString ->                              -- title : TBasicType TUTF8
    IO ()

-- | Sets the title of the @GtkNativeDialog.@
nativeDialogSetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a @GtkNativeDialog@
    -> T.Text
    -- ^ /@title@/: title of the dialog
    -> m ()
nativeDialogSetTitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNativeDialog a) =>
a -> Text -> m ()
nativeDialogSetTitle a
self Text
title = 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 NativeDialog
self' <- a -> IO (Ptr NativeDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
title' <- Text -> IO CString
textToCString Text
title
    Ptr NativeDialog -> CString -> IO ()
gtk_native_dialog_set_title Ptr NativeDialog
self' CString
title'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
title'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NativeDialogSetTitleMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsNativeDialog a) => O.OverloadedMethod NativeDialogSetTitleMethodInfo a signature where
    overloadedMethod = nativeDialogSetTitle

instance O.OverloadedMethodInfo NativeDialogSetTitleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.NativeDialog.nativeDialogSetTitle",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-NativeDialog.html#v:nativeDialogSetTitle"
        })


#endif

-- method NativeDialog::set_transient_for
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "NativeDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkNativeDialog`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parent"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "parent window" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_native_dialog_set_transient_for" gtk_native_dialog_set_transient_for :: 
    Ptr NativeDialog ->                     -- self : TInterface (Name {namespace = "Gtk", name = "NativeDialog"})
    Ptr Gtk.Window.Window ->                -- parent : TInterface (Name {namespace = "Gtk", name = "Window"})
    IO ()

-- | Dialog windows should be set transient for the main application
-- window they were spawned from.
-- 
-- This allows window managers to e.g. keep the dialog on top of the
-- main window, or center the dialog over the main window.
-- 
-- Passing 'P.Nothing' for /@parent@/ unsets the current transient window.
nativeDialogSetTransientFor ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a, Gtk.Window.IsWindow b) =>
    a
    -- ^ /@self@/: a @GtkNativeDialog@
    -> Maybe (b)
    -- ^ /@parent@/: parent window
    -> m ()
nativeDialogSetTransientFor :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsNativeDialog a, IsWindow b) =>
a -> Maybe b -> m ()
nativeDialogSetTransientFor a
self Maybe b
parent = 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 NativeDialog
self' <- a -> IO (Ptr NativeDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Window
maybeParent <- case Maybe b
parent of
        Maybe b
Nothing -> Ptr Window -> IO (Ptr Window)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
forall a. Ptr a
nullPtr
        Just b
jParent -> do
            Ptr Window
jParent' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jParent
            Ptr Window -> IO (Ptr Window)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
jParent'
    Ptr NativeDialog -> Ptr Window -> IO ()
gtk_native_dialog_set_transient_for Ptr NativeDialog
self' Ptr Window
maybeParent
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
parent b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NativeDialogSetTransientForMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsNativeDialog a, Gtk.Window.IsWindow b) => O.OverloadedMethod NativeDialogSetTransientForMethodInfo a signature where
    overloadedMethod = nativeDialogSetTransientFor

instance O.OverloadedMethodInfo NativeDialogSetTransientForMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.NativeDialog.nativeDialogSetTransientFor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-NativeDialog.html#v:nativeDialogSetTransientFor"
        })


#endif

-- method NativeDialog::show
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "NativeDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkNativeDialog`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_native_dialog_show" gtk_native_dialog_show :: 
    Ptr NativeDialog ->                     -- self : TInterface (Name {namespace = "Gtk", name = "NativeDialog"})
    IO ()

-- | Shows the dialog on the display.
-- 
-- When the user accepts the state of the dialog the dialog will
-- be automatically hidden and the [NativeDialog::response]("GI.Gtk.Objects.NativeDialog#g:signal:response")
-- signal will be emitted.
-- 
-- Multiple calls while the dialog is visible will be ignored.
nativeDialogShow ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a @GtkNativeDialog@
    -> m ()
nativeDialogShow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNativeDialog a) =>
a -> m ()
nativeDialogShow a
self = 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 NativeDialog
self' <- a -> IO (Ptr NativeDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr NativeDialog -> IO ()
gtk_native_dialog_show Ptr NativeDialog
self'
    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 NativeDialogShowMethodInfo
instance (signature ~ (m ()), MonadIO m, IsNativeDialog a) => O.OverloadedMethod NativeDialogShowMethodInfo a signature where
    overloadedMethod = nativeDialogShow

instance O.OverloadedMethodInfo NativeDialogShowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.NativeDialog.nativeDialogShow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-NativeDialog.html#v:nativeDialogShow"
        })


#endif