{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Native dialogs are platform dialogs that don\'t use t'GI.Gtk.Objects.Dialog.Dialog' or
-- t'GI.Gtk.Objects.Window.Window'. 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 t'GI.Gtk.Objects.NativeDialog.NativeDialog'
-- 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 [response]("GI.Gtk.Objects.NativeDialog#g:signal:response") signal when the user finished
-- with the dialog.
-- 
-- There is also a 'GI.Gtk.Objects.NativeDialog.nativeDialogRun' helper that makes it easy
-- to run any native dialog in a modal way with a recursive mainloop,
-- similar to 'GI.Gtk.Objects.Dialog.dialogRun'.

#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
-- ** Overloaded methods #method:Overloaded methods#

#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                        ,


-- ** run #method:run#

#if defined(ENABLE_OVERLOADING)
    NativeDialogRunMethodInfo               ,
#endif
    nativeDialogRun                         ,


-- ** 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.
-- 
-- /Since: 3.20/

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


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

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

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


-- ** visible #attr:visible#
-- | Whether the window is currenlty visible.
-- 
-- /Since: 3.20/

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




 -- * Signals
-- ** response #signal:response#

    C_NativeDialogResponseCallback          ,
    NativeDialogResponseCallback            ,
#if defined(ENABLE_OVERLOADING)
    NativeDialogResponseSignalInfo          ,
#endif
    afterNativeDialogResponse               ,
    genClosure_NativeDialogResponse         ,
    mk_NativeDialogResponseCallback         ,
    noNativeDialogResponseCallback          ,
    onNativeDialogResponse                  ,
    wrap_NativeDialogResponseCallback       ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified 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
/= :: NativeDialog -> NativeDialog -> Bool
$c/= :: NativeDialog -> NativeDialog -> Bool
== :: NativeDialog -> NativeDialog -> Bool
$c== :: 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

-- | Convert 'NativeDialog' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue NativeDialog where
    toGValue :: NativeDialog -> IO GValue
toGValue NativeDialog
o = do
        GType
gtype <- IO GType
c_gtk_native_dialog_get_type
        NativeDialog -> (Ptr NativeDialog -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr NativeDialog
o (GType
-> (GValue -> Ptr NativeDialog -> IO ())
-> Ptr NativeDialog
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr NativeDialog -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO NativeDialog
fromGValue GValue
gv = do
        Ptr NativeDialog
ptr <- GValue -> IO (Ptr NativeDialog)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr NativeDialog)
        (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
        
    

-- | 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 :: (MonadIO m, IsNativeDialog o) => o -> m NativeDialog
toNativeDialog :: o -> m NativeDialog
toNativeDialog = IO NativeDialog -> m NativeDialog
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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'
unsafeCastTo ManagedPtr NativeDialog -> NativeDialog
NativeDialog

#if defined(ENABLE_OVERLOADING)
type family ResolveNativeDialogMethod (t :: Symbol) (o :: *) :: * 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 "run" o = NativeDialogRunMethodInfo
    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.MethodInfo 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

#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.
-- 
-- /Since: 3.20/
type NativeDialogResponseCallback =
    Int32
    -- ^ /@responseId@/: the response ID
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `NativeDialogResponseCallback`@.
noNativeDialogResponseCallback :: Maybe NativeDialogResponseCallback
noNativeDialogResponseCallback :: Maybe NativeDialogResponseCallback
noNativeDialogResponseCallback = Maybe NativeDialogResponseCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_NativeDialogResponseCallback =
    Ptr () ->                               -- 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 the callback into a `GClosure`.
genClosure_NativeDialogResponse :: MonadIO m => NativeDialogResponseCallback -> m (GClosure C_NativeDialogResponseCallback)
genClosure_NativeDialogResponse :: NativeDialogResponseCallback
-> m (GClosure C_NativeDialogResponseCallback)
genClosure_NativeDialogResponse NativeDialogResponseCallback
cb = IO (GClosure C_NativeDialogResponseCallback)
-> m (GClosure C_NativeDialogResponseCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_NativeDialogResponseCallback)
 -> m (GClosure C_NativeDialogResponseCallback))
-> IO (GClosure C_NativeDialogResponseCallback)
-> m (GClosure C_NativeDialogResponseCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_NativeDialogResponseCallback
cb' = NativeDialogResponseCallback -> C_NativeDialogResponseCallback
wrap_NativeDialogResponseCallback NativeDialogResponseCallback
cb
    C_NativeDialogResponseCallback
-> IO (FunPtr C_NativeDialogResponseCallback)
mk_NativeDialogResponseCallback C_NativeDialogResponseCallback
cb' IO (FunPtr C_NativeDialogResponseCallback)
-> (FunPtr C_NativeDialogResponseCallback
    -> IO (GClosure C_NativeDialogResponseCallback))
-> IO (GClosure C_NativeDialogResponseCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_NativeDialogResponseCallback
-> IO (GClosure C_NativeDialogResponseCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `NativeDialogResponseCallback` into a `C_NativeDialogResponseCallback`.
wrap_NativeDialogResponseCallback ::
    NativeDialogResponseCallback ->
    C_NativeDialogResponseCallback
wrap_NativeDialogResponseCallback :: NativeDialogResponseCallback -> C_NativeDialogResponseCallback
wrap_NativeDialogResponseCallback NativeDialogResponseCallback
_cb Ptr ()
_ Int32
responseId Ptr ()
_ = do
    NativeDialogResponseCallback
_cb  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 -> NativeDialogResponseCallback -> m SignalHandlerId
onNativeDialogResponse :: a -> NativeDialogResponseCallback -> m SignalHandlerId
onNativeDialogResponse a
obj NativeDialogResponseCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_NativeDialogResponseCallback
cb' = NativeDialogResponseCallback -> C_NativeDialogResponseCallback
wrap_NativeDialogResponseCallback NativeDialogResponseCallback
cb
    FunPtr C_NativeDialogResponseCallback
cb'' <- C_NativeDialogResponseCallback
-> IO (FunPtr C_NativeDialogResponseCallback)
mk_NativeDialogResponseCallback C_NativeDialogResponseCallback
cb'
    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
cb'' 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
-- @
-- 
-- 
afterNativeDialogResponse :: (IsNativeDialog a, MonadIO m) => a -> NativeDialogResponseCallback -> m SignalHandlerId
afterNativeDialogResponse :: a -> NativeDialogResponseCallback -> m SignalHandlerId
afterNativeDialogResponse a
obj NativeDialogResponseCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_NativeDialogResponseCallback
cb' = NativeDialogResponseCallback -> C_NativeDialogResponseCallback
wrap_NativeDialogResponseCallback NativeDialogResponseCallback
cb
    FunPtr C_NativeDialogResponseCallback
cb'' <- C_NativeDialogResponseCallback
-> IO (FunPtr C_NativeDialogResponseCallback)
mk_NativeDialogResponseCallback C_NativeDialogResponseCallback
cb'
    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
cb'' 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

#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 :: o -> m Bool
getNativeDialogModal o
obj = IO Bool -> m Bool
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
$ 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 :: o -> Bool -> m ()
setNativeDialogModal o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ 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 :: Bool -> m (GValueConstruct o)
constructNativeDialogModal Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#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 :: o -> m (Maybe Text)
getNativeDialogTitle o
obj = IO (Maybe Text) -> m (Maybe Text)
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
$ 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 :: o -> Text -> m ()
setNativeDialogTitle o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"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 :: Text -> m (GValueConstruct o)
constructNativeDialogTitle Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#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 :: o -> m (Maybe Window)
getNativeDialogTransientFor o
obj = IO (Maybe Window) -> m (Maybe Window)
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
$ 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 :: o -> a -> m ()
setNativeDialogTransientFor o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ 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 :: a -> m (GValueConstruct o)
constructNativeDialogTransientFor a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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 :: o -> m ()
clearNativeDialogTransientFor o
obj = IO () -> m ()
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
#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 :: o -> m Bool
getNativeDialogVisible o
obj = IO Bool -> m Bool
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
$ 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 :: o -> Bool -> m ()
setNativeDialogVisible o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ 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 :: Bool -> m (GValueConstruct o)
constructNativeDialogVisible Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#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, *)])
#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, *)])

#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 t'GI.Gtk.Objects.NativeDialog.NativeDialog'.
-- 
-- /Since: 3.20/
nativeDialogDestroy ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.NativeDialog.NativeDialog'
    -> m ()
nativeDialogDestroy :: a -> m ()
nativeDialogDestroy a
self = IO () -> m ()
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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NativeDialogDestroyMethodInfo
instance (signature ~ (m ()), MonadIO m, IsNativeDialog a) => O.MethodInfo NativeDialogDestroyMethodInfo a signature where
    overloadedMethod = 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. See 'GI.Gtk.Objects.NativeDialog.nativeDialogSetModal'.
-- 
-- /Since: 3.20/
nativeDialogGetModal ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.NativeDialog.NativeDialog'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the dialog is set to be modal
nativeDialogGetModal :: a -> m Bool
nativeDialogGetModal a
self = IO Bool -> m Bool
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 (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.MethodInfo NativeDialogGetModalMethodInfo a signature where
    overloadedMethod = 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 t'GI.Gtk.Objects.NativeDialog.NativeDialog'.
-- 
-- /Since: 3.20/
nativeDialogGetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.NativeDialog.NativeDialog'
    -> 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 :: a -> m (Maybe Text)
nativeDialogGetTitle a
self = IO (Maybe Text) -> m (Maybe Text)
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 (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 (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.MethodInfo NativeDialogGetTitleMethodInfo a signature where
    overloadedMethod = 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. See
-- 'GI.Gtk.Objects.NativeDialog.nativeDialogSetTransientFor'.
-- 
-- /Since: 3.20/
nativeDialogGetTransientFor ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.NativeDialog.NativeDialog'
    -> m (Maybe Gtk.Window.Window)
    -- ^ __Returns:__ the transient parent for this window,
    -- or 'P.Nothing' if no transient parent has been set.
nativeDialogGetTransientFor :: a -> m (Maybe Window)
nativeDialogGetTransientFor a
self = IO (Maybe Window) -> m (Maybe Window)
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 (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 (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.MethodInfo NativeDialogGetTransientForMethodInfo a signature where
    overloadedMethod = 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.
-- 
-- /Since: 3.20/
nativeDialogGetVisible ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.NativeDialog.NativeDialog'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the dialog is visible
nativeDialogGetVisible :: a -> m Bool
nativeDialogGetVisible a
self = IO Bool -> m Bool
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 (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.MethodInfo NativeDialogGetVisibleMethodInfo a signature where
    overloadedMethod = 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 visilbe, aborting any interaction. Once this
-- is called the  [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.
-- 
-- /Since: 3.20/
nativeDialogHide ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.NativeDialog.NativeDialog'
    -> m ()
nativeDialogHide :: a -> m ()
nativeDialogHide a
self = IO () -> m ()
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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NativeDialogHideMethodInfo
instance (signature ~ (m ()), MonadIO m, IsNativeDialog a) => O.MethodInfo NativeDialogHideMethodInfo a signature where
    overloadedMethod = nativeDialogHide

#endif

-- method NativeDialog::run
-- 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 TInt)
-- throws : False
-- Skip return : False

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

-- | Blocks in a recursive main loop until /@self@/ emits the
-- [response]("GI.Gtk.Objects.NativeDialog#g:signal:response") signal. It then returns the response ID
-- from the [response](#g:signal:response) signal emission.
-- 
-- Before entering the recursive main loop, 'GI.Gtk.Objects.NativeDialog.nativeDialogRun'
-- calls 'GI.Gtk.Objects.NativeDialog.nativeDialogShow' on the dialog for you.
-- 
-- After 'GI.Gtk.Objects.NativeDialog.nativeDialogRun' returns, then dialog will be hidden.
-- 
-- Typical usage of this function might be:
-- 
-- === /C code/
-- >
-- >  gint result = gtk_native_dialog_run (GTK_NATIVE_DIALOG (dialog));
-- >  switch (result)
-- >    {
-- >      case GTK_RESPONSE_ACCEPT:
-- >         do_application_specific_something ();
-- >         break;
-- >      default:
-- >         do_nothing_since_dialog_was_cancelled ();
-- >         break;
-- >    }
-- >  g_object_unref (dialog);
-- 
-- 
-- Note that even though the recursive main loop gives the effect of a
-- modal dialog (it prevents the user from interacting with other
-- windows in the same window group while the dialog is run), callbacks
-- such as timeouts, IO channel watches, DND drops, etc, will
-- be triggered during a @/gtk_nautilus_dialog_run()/@ call.
-- 
-- /Since: 3.20/
nativeDialogRun ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.NativeDialog.NativeDialog'
    -> m Int32
    -- ^ __Returns:__ response ID
nativeDialogRun :: a -> m Int32
nativeDialogRun a
self = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr NativeDialog
self' <- a -> IO (Ptr NativeDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Int32
result <- Ptr NativeDialog -> IO Int32
gtk_native_dialog_run Ptr NativeDialog
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data NativeDialogRunMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsNativeDialog a) => O.MethodInfo NativeDialogRunMethodInfo a signature where
    overloadedMethod = nativeDialogRun

#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][gtk-X11-arch]
-- will then disallow lowering the dialog below the parent.
-- 
-- /Since: 3.20/
nativeDialogSetModal ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.NativeDialog.NativeDialog'
    -> Bool
    -- ^ /@modal@/: whether the window is modal
    -> m ()
nativeDialogSetModal :: a -> Bool -> m ()
nativeDialogSetModal a
self Bool
modal = IO () -> m ()
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
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
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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NativeDialogSetModalMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsNativeDialog a) => O.MethodInfo NativeDialogSetModalMethodInfo a signature where
    overloadedMethod = 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 t'GI.Gtk.Objects.NativeDialog.NativeDialog'.
-- 
-- /Since: 3.20/
nativeDialogSetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.NativeDialog.NativeDialog'
    -> T.Text
    -- ^ /@title@/: title of the dialog
    -> m ()
nativeDialogSetTitle :: a -> Text -> m ()
nativeDialogSetTitle a
self Text
title = IO () -> m ()
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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NativeDialogSetTitleMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsNativeDialog a) => O.MethodInfo NativeDialogSetTitleMethodInfo a signature where
    overloadedMethod = 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, or %NULL"
--                 , 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][gtk-X11-arch] 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.
-- 
-- /Since: 3.20/
nativeDialogSetTransientFor ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a, Gtk.Window.IsWindow b) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.NativeDialog.NativeDialog'
    -> Maybe (b)
    -- ^ /@parent@/: parent window, or 'P.Nothing'
    -> m ()
nativeDialogSetTransientFor :: a -> Maybe b -> m ()
nativeDialogSetTransientFor a
self Maybe b
parent = IO () -> m ()
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 (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 (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 (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.MethodInfo NativeDialogSetTransientForMethodInfo a signature where
    overloadedMethod = 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, allowing the user to interact with
-- it. When the user accepts the state of the dialog the dialog will
-- be automatically hidden and the [response]("GI.Gtk.Objects.NativeDialog#g:signal:response") signal
-- will be emitted.
-- 
-- Multiple calls while the dialog is visible will be ignored.
-- 
-- /Since: 3.20/
nativeDialogShow ::
    (B.CallStack.HasCallStack, MonadIO m, IsNativeDialog a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.NativeDialog.NativeDialog'
    -> m ()
nativeDialogShow :: a -> m ()
nativeDialogShow a
self = IO () -> m ()
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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data NativeDialogShowMethodInfo
instance (signature ~ (m ()), MonadIO m, IsNativeDialog a) => O.MethodInfo NativeDialogShowMethodInfo a signature where
    overloadedMethod = nativeDialogShow

#endif