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


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A high-level API for writing applications.
-- 
-- @GtkApplication@ supports many aspects of writing a GTK application
-- in a convenient fashion, without enforcing a one-size-fits-all model.
-- 
-- Currently, it handles GTK initialization, application uniqueness, session
-- management, provides some basic scriptability and desktop shell integration
-- by exporting actions and menus and manages a list of toplevel windows whose
-- life-cycle is automatically tied to the life-cycle of your application.
-- 
-- While @GtkApplication@ works fine with plain t'GI.Gtk.Objects.Window.Window's,
-- it is recommended to use it together with t'GI.Gtk.Objects.ApplicationWindow.ApplicationWindow'.
-- 
-- == Automatic resources
-- 
-- @GtkApplication@ will automatically load menus from the @GtkBuilder@
-- resource located at \"gtk\/menus.ui\", relative to the application\'s
-- resource base path (see 'GI.Gio.Objects.Application.applicationSetResourceBasePath').
-- The menu with the ID \"menubar\" is taken as the application\'s
-- menubar. Additional menus (most interesting submenus) can be named
-- and accessed via 'GI.Gtk.Objects.Application.applicationGetMenuById' which allows for
-- dynamic population of a part of the menu structure.
-- 
-- Note that automatic resource loading uses the resource base path
-- that is set at construction time and will not work if the resource
-- base path is changed at a later time.
-- 
-- It is also possible to provide the menubar manually using
-- 'GI.Gtk.Objects.Application.applicationSetMenubar'.
-- 
-- @GtkApplication@ will also automatically setup an icon search path for
-- the default icon theme by appending \"icons\" to the resource base
-- path. This allows your application to easily store its icons as
-- resources. See 'GI.Gtk.Objects.IconTheme.iconThemeAddResourcePath' for more
-- information.
-- 
-- If there is a resource located at @gtk\/help-overlay.ui@ which
-- defines a t'GI.Gtk.Objects.ShortcutsWindow.ShortcutsWindow' with ID @help_overlay@ then
-- @GtkApplication@ associates an instance of this shortcuts window with
-- each t'GI.Gtk.Objects.ApplicationWindow.ApplicationWindow' and sets up the keyboard accelerator
-- \<kbd>Control\<\/kbd>+\<kbd>?\<\/kbd> to open it. To create a menu item that
-- displays the shortcuts window, associate the item with the action
-- @win.show-help-overlay@.
-- 
-- @GtkApplication@ will also automatically set the application id as the
-- default window icon. Use 'GI.Gtk.Objects.Window.windowSetDefaultIconName' or
-- [Window:iconName]("GI.Gtk.Objects.Window#g:attr:iconName") to override that behavior.
-- 
-- == A simple application
-- 
-- <https://gitlab.gnome.org/GNOME/gtk/tree/main/examples/bp/bloatpad.c A simple example>
-- is available in the GTK source code repository
-- 
-- @GtkApplication@ optionally registers with a session manager of the
-- users session (if you set the [Application:registerSession]("GI.Gtk.Objects.Application#g:attr:registerSession")
-- property) and offers various functionality related to the session
-- life-cycle.
-- 
-- An application can block various ways to end the session with
-- the 'GI.Gtk.Objects.Application.applicationInhibit' function. Typical use cases for
-- this kind of inhibiting are long-running, uninterruptible operations,
-- such as burning a CD or performing a disk backup. The session
-- manager may not honor the inhibitor, but it can be expected to
-- inform the user about the negative consequences of ending the
-- session while inhibitors are present.
-- 
-- == See Also
-- 
-- * <https://developer.gnome.org/documentation/tutorials/application.html Using GtkApplication>
-- * <https://docs.gtk.org/gtk4/getting_started.html#basics Getting Started with GTK: Basics>
-- 

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

module GI.Gtk.Objects.Application
    ( 

-- * Exported types
    Application(..)                         ,
    IsApplication                           ,
    toApplication                           ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [actionAdded]("GI.Gio.Interfaces.ActionGroup#g:method:actionAdded"), [actionEnabledChanged]("GI.Gio.Interfaces.ActionGroup#g:method:actionEnabledChanged"), [actionRemoved]("GI.Gio.Interfaces.ActionGroup#g:method:actionRemoved"), [actionStateChanged]("GI.Gio.Interfaces.ActionGroup#g:method:actionStateChanged"), [activate]("GI.Gio.Objects.Application#g:method:activate"), [activateAction]("GI.Gio.Interfaces.ActionGroup#g:method:activateAction"), [addAction]("GI.Gio.Interfaces.ActionMap#g:method:addAction"), [addActionEntries]("GI.Gio.Interfaces.ActionMap#g:method:addActionEntries"), [addMainOption]("GI.Gio.Objects.Application#g:method:addMainOption"), [addMainOptionEntries]("GI.Gio.Objects.Application#g:method:addMainOptionEntries"), [addOptionGroup]("GI.Gio.Objects.Application#g:method:addOptionGroup"), [addWindow]("GI.Gtk.Objects.Application#g:method:addWindow"), [bindBusyProperty]("GI.Gio.Objects.Application#g:method:bindBusyProperty"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [changeActionState]("GI.Gio.Interfaces.ActionGroup#g:method:changeActionState"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hasAction]("GI.Gio.Interfaces.ActionGroup#g:method:hasAction"), [hold]("GI.Gio.Objects.Application#g:method:hold"), [inhibit]("GI.Gtk.Objects.Application#g:method:inhibit"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [listActionDescriptions]("GI.Gtk.Objects.Application#g:method:listActionDescriptions"), [listActions]("GI.Gio.Interfaces.ActionGroup#g:method:listActions"), [lookupAction]("GI.Gio.Interfaces.ActionMap#g:method:lookupAction"), [markBusy]("GI.Gio.Objects.Application#g:method:markBusy"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [open]("GI.Gio.Objects.Application#g:method:open"), [queryAction]("GI.Gio.Interfaces.ActionGroup#g:method:queryAction"), [quit]("GI.Gio.Objects.Application#g:method:quit"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [register]("GI.Gio.Objects.Application#g:method:register"), [release]("GI.Gio.Objects.Application#g:method:release"), [removeAction]("GI.Gio.Interfaces.ActionMap#g:method:removeAction"), [removeActionEntries]("GI.Gio.Interfaces.ActionMap#g:method:removeActionEntries"), [removeWindow]("GI.Gtk.Objects.Application#g:method:removeWindow"), [run]("GI.Gio.Objects.Application#g:method:run"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [sendNotification]("GI.Gio.Objects.Application#g:method:sendNotification"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unbindBusyProperty]("GI.Gio.Objects.Application#g:method:unbindBusyProperty"), [uninhibit]("GI.Gtk.Objects.Application#g:method:uninhibit"), [unmarkBusy]("GI.Gio.Objects.Application#g:method:unmarkBusy"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure"), [withdrawNotification]("GI.Gio.Objects.Application#g:method:withdrawNotification").
-- 
-- ==== Getters
-- [getAccelsForAction]("GI.Gtk.Objects.Application#g:method:getAccelsForAction"), [getActionEnabled]("GI.Gio.Interfaces.ActionGroup#g:method:getActionEnabled"), [getActionParameterType]("GI.Gio.Interfaces.ActionGroup#g:method:getActionParameterType"), [getActionState]("GI.Gio.Interfaces.ActionGroup#g:method:getActionState"), [getActionStateHint]("GI.Gio.Interfaces.ActionGroup#g:method:getActionStateHint"), [getActionStateType]("GI.Gio.Interfaces.ActionGroup#g:method:getActionStateType"), [getActionsForAccel]("GI.Gtk.Objects.Application#g:method:getActionsForAccel"), [getActiveWindow]("GI.Gtk.Objects.Application#g:method:getActiveWindow"), [getApplicationId]("GI.Gio.Objects.Application#g:method:getApplicationId"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDbusConnection]("GI.Gio.Objects.Application#g:method:getDbusConnection"), [getDbusObjectPath]("GI.Gio.Objects.Application#g:method:getDbusObjectPath"), [getFlags]("GI.Gio.Objects.Application#g:method:getFlags"), [getInactivityTimeout]("GI.Gio.Objects.Application#g:method:getInactivityTimeout"), [getIsBusy]("GI.Gio.Objects.Application#g:method:getIsBusy"), [getIsRegistered]("GI.Gio.Objects.Application#g:method:getIsRegistered"), [getIsRemote]("GI.Gio.Objects.Application#g:method:getIsRemote"), [getMenuById]("GI.Gtk.Objects.Application#g:method:getMenuById"), [getMenubar]("GI.Gtk.Objects.Application#g:method:getMenubar"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getResourceBasePath]("GI.Gio.Objects.Application#g:method:getResourceBasePath"), [getVersion]("GI.Gio.Objects.Application#g:method:getVersion"), [getWindowById]("GI.Gtk.Objects.Application#g:method:getWindowById"), [getWindows]("GI.Gtk.Objects.Application#g:method:getWindows").
-- 
-- ==== Setters
-- [setAccelsForAction]("GI.Gtk.Objects.Application#g:method:setAccelsForAction"), [setActionGroup]("GI.Gio.Objects.Application#g:method:setActionGroup"), [setApplicationId]("GI.Gio.Objects.Application#g:method:setApplicationId"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDefault]("GI.Gio.Objects.Application#g:method:setDefault"), [setFlags]("GI.Gio.Objects.Application#g:method:setFlags"), [setInactivityTimeout]("GI.Gio.Objects.Application#g:method:setInactivityTimeout"), [setMenubar]("GI.Gtk.Objects.Application#g:method:setMenubar"), [setOptionContextDescription]("GI.Gio.Objects.Application#g:method:setOptionContextDescription"), [setOptionContextParameterString]("GI.Gio.Objects.Application#g:method:setOptionContextParameterString"), [setOptionContextSummary]("GI.Gio.Objects.Application#g:method:setOptionContextSummary"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setResourceBasePath]("GI.Gio.Objects.Application#g:method:setResourceBasePath"), [setVersion]("GI.Gio.Objects.Application#g:method:setVersion").

#if defined(ENABLE_OVERLOADING)
    ResolveApplicationMethod                ,
#endif

-- ** addWindow #method:addWindow#

#if defined(ENABLE_OVERLOADING)
    ApplicationAddWindowMethodInfo          ,
#endif
    applicationAddWindow                    ,


-- ** getAccelsForAction #method:getAccelsForAction#

#if defined(ENABLE_OVERLOADING)
    ApplicationGetAccelsForActionMethodInfo ,
#endif
    applicationGetAccelsForAction           ,


-- ** getActionsForAccel #method:getActionsForAccel#

#if defined(ENABLE_OVERLOADING)
    ApplicationGetActionsForAccelMethodInfo ,
#endif
    applicationGetActionsForAccel           ,


-- ** getActiveWindow #method:getActiveWindow#

#if defined(ENABLE_OVERLOADING)
    ApplicationGetActiveWindowMethodInfo    ,
#endif
    applicationGetActiveWindow              ,


-- ** getMenuById #method:getMenuById#

#if defined(ENABLE_OVERLOADING)
    ApplicationGetMenuByIdMethodInfo        ,
#endif
    applicationGetMenuById                  ,


-- ** getMenubar #method:getMenubar#

#if defined(ENABLE_OVERLOADING)
    ApplicationGetMenubarMethodInfo         ,
#endif
    applicationGetMenubar                   ,


-- ** getWindowById #method:getWindowById#

#if defined(ENABLE_OVERLOADING)
    ApplicationGetWindowByIdMethodInfo      ,
#endif
    applicationGetWindowById                ,


-- ** getWindows #method:getWindows#

#if defined(ENABLE_OVERLOADING)
    ApplicationGetWindowsMethodInfo         ,
#endif
    applicationGetWindows                   ,


-- ** inhibit #method:inhibit#

#if defined(ENABLE_OVERLOADING)
    ApplicationInhibitMethodInfo            ,
#endif
    applicationInhibit                      ,


-- ** listActionDescriptions #method:listActionDescriptions#

#if defined(ENABLE_OVERLOADING)
    ApplicationListActionDescriptionsMethodInfo,
#endif
    applicationListActionDescriptions       ,


-- ** new #method:new#

    applicationNew                          ,


-- ** removeWindow #method:removeWindow#

#if defined(ENABLE_OVERLOADING)
    ApplicationRemoveWindowMethodInfo       ,
#endif
    applicationRemoveWindow                 ,


-- ** setAccelsForAction #method:setAccelsForAction#

#if defined(ENABLE_OVERLOADING)
    ApplicationSetAccelsForActionMethodInfo ,
#endif
    applicationSetAccelsForAction           ,


-- ** setMenubar #method:setMenubar#

#if defined(ENABLE_OVERLOADING)
    ApplicationSetMenubarMethodInfo         ,
#endif
    applicationSetMenubar                   ,


-- ** uninhibit #method:uninhibit#

#if defined(ENABLE_OVERLOADING)
    ApplicationUninhibitMethodInfo          ,
#endif
    applicationUninhibit                    ,




 -- * Properties


-- ** activeWindow #attr:activeWindow#
-- | The currently focused window of the application.

#if defined(ENABLE_OVERLOADING)
    ApplicationActiveWindowPropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    applicationActiveWindow                 ,
#endif
    getApplicationActiveWindow              ,


-- ** menubar #attr:menubar#
-- | The menu model to be used for the application\'s menu bar.

#if defined(ENABLE_OVERLOADING)
    ApplicationMenubarPropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    applicationMenubar                      ,
#endif
    clearApplicationMenubar                 ,
    constructApplicationMenubar             ,
    getApplicationMenubar                   ,
    setApplicationMenubar                   ,


-- ** registerSession #attr:registerSession#
-- | Set this property to true to register with the session manager.
-- 
-- This will make GTK track the session state (such as the
-- [Application:screensaverActive]("GI.Gtk.Objects.Application#g:attr:screensaverActive") property).

#if defined(ENABLE_OVERLOADING)
    ApplicationRegisterSessionPropertyInfo  ,
#endif
#if defined(ENABLE_OVERLOADING)
    applicationRegisterSession              ,
#endif
    constructApplicationRegisterSession     ,
    getApplicationRegisterSession           ,
    setApplicationRegisterSession           ,


-- ** screensaverActive #attr:screensaverActive#
-- | This property is true if GTK believes that the screensaver
-- is currently active.
-- 
-- GTK only tracks session state (including this) when
-- [Application:registerSession]("GI.Gtk.Objects.Application#g:attr:registerSession") is set to true.
-- 
-- Tracking the screensaver state is currently only supported on
-- Linux.

#if defined(ENABLE_OVERLOADING)
    ApplicationScreensaverActivePropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    applicationScreensaverActive            ,
#endif
    getApplicationScreensaverActive         ,




 -- * Signals


-- ** queryEnd #signal:queryEnd#

    ApplicationQueryEndCallback             ,
#if defined(ENABLE_OVERLOADING)
    ApplicationQueryEndSignalInfo           ,
#endif
    afterApplicationQueryEnd                ,
    onApplicationQueryEnd                   ,


-- ** windowAdded #signal:windowAdded#

    ApplicationWindowAddedCallback          ,
#if defined(ENABLE_OVERLOADING)
    ApplicationWindowAddedSignalInfo        ,
#endif
    afterApplicationWindowAdded             ,
    onApplicationWindowAdded                ,


-- ** windowRemoved #signal:windowRemoved#

    ApplicationWindowRemovedCallback        ,
#if defined(ENABLE_OVERLOADING)
    ApplicationWindowRemovedSignalInfo      ,
#endif
    afterApplicationWindowRemoved           ,
    onApplicationWindowRemoved              ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Flags as Gdk.Flags
import qualified GI.Gdk.Interfaces.Paintable as Gdk.Paintable
import qualified GI.Gdk.Objects.Clipboard as Gdk.Clipboard
import qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import qualified GI.Gdk.Objects.Device as Gdk.Device
import qualified GI.Gdk.Objects.Display as Gdk.Display
import qualified GI.Gdk.Objects.Event as Gdk.Event
import qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import qualified GI.Gdk.Objects.Monitor as Gdk.Monitor
import qualified GI.Gdk.Objects.Snapshot as Gdk.Snapshot
import qualified GI.Gdk.Objects.Surface as Gdk.Surface
import qualified GI.Gdk.Objects.Texture as Gdk.Texture
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import qualified GI.Gio.Flags as Gio.Flags
import qualified GI.Gio.Interfaces.ActionGroup as Gio.ActionGroup
import qualified GI.Gio.Interfaces.ActionMap as Gio.ActionMap
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Gio.Objects.Application as Gio.Application
import qualified GI.Gio.Objects.Menu as Gio.Menu
import qualified GI.Gio.Objects.MenuModel as Gio.MenuModel
import qualified GI.Graphene.Structs.Matrix as Graphene.Matrix
import qualified GI.Graphene.Structs.Point as Graphene.Point
import qualified GI.Graphene.Structs.Point3D as Graphene.Point3D
import qualified GI.Graphene.Structs.Rect as Graphene.Rect
import qualified GI.Graphene.Structs.Size as Graphene.Size
import qualified GI.Graphene.Structs.Vec3 as Graphene.Vec3
import qualified GI.Graphene.Structs.Vec4 as Graphene.Vec4
import qualified GI.Gsk.Enums as Gsk.Enums
import qualified GI.Gsk.Objects.GLShader as Gsk.GLShader
import qualified GI.Gsk.Objects.RenderNode as Gsk.RenderNode
import qualified GI.Gsk.Objects.Renderer as Gsk.Renderer
import qualified GI.Gsk.Structs.ColorStop as Gsk.ColorStop
import qualified GI.Gsk.Structs.Path as Gsk.Path
import qualified GI.Gsk.Structs.RoundedRect as Gsk.RoundedRect
import qualified GI.Gsk.Structs.Shadow as Gsk.Shadow
import qualified GI.Gsk.Structs.Stroke as Gsk.Stroke
import qualified GI.Gsk.Structs.Transform as Gsk.Transform
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Native as Gtk.Native
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Root as Gtk.Root
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ShortcutManager as Gtk.ShortcutManager
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.StyleProvider as Gtk.StyleProvider
import {-# SOURCE #-} qualified GI.Gtk.Objects.ATContext as Gtk.ATContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.EventController as Gtk.EventController
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutChild as Gtk.LayoutChild
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutManager as Gtk.LayoutManager
import {-# SOURCE #-} qualified GI.Gtk.Objects.Settings as Gtk.Settings
import {-# SOURCE #-} qualified GI.Gtk.Objects.Snapshot as Gtk.Snapshot
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleContext as Gtk.StyleContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.Tooltip as Gtk.Tooltip
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Objects.Window as Gtk.Window
import {-# SOURCE #-} qualified GI.Gtk.Objects.WindowGroup as Gtk.WindowGroup
import {-# SOURCE #-} qualified GI.Gtk.Structs.Border as Gtk.Border
import {-# SOURCE #-} qualified GI.Gtk.Structs.Requisition as Gtk.Requisition
import qualified GI.Pango.Enums as Pango.Enums
import qualified GI.Pango.Objects.Context as Pango.Context
import qualified GI.Pango.Objects.FontMap as Pango.FontMap
import qualified GI.Pango.Objects.Layout as Pango.Layout

#else
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Flags as Gio.Flags
import qualified GI.Gio.Interfaces.ActionGroup as Gio.ActionGroup
import qualified GI.Gio.Interfaces.ActionMap as Gio.ActionMap
import qualified GI.Gio.Objects.Application as Gio.Application
import qualified GI.Gio.Objects.Menu as Gio.Menu
import qualified GI.Gio.Objects.MenuModel as Gio.MenuModel
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Objects.Window as Gtk.Window

#endif

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

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

foreign import ccall "gtk_application_get_type"
    c_gtk_application_get_type :: IO B.Types.GType

instance B.Types.TypedObject Application where
    glibType :: IO GType
glibType = IO GType
c_gtk_application_get_type

instance B.Types.GObject Application

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

instance O.HasParentTypes Application
type instance O.ParentTypes Application = '[Gio.Application.Application, GObject.Object.Object, Gio.ActionGroup.ActionGroup, Gio.ActionMap.ActionMap]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveApplicationMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveApplicationMethod "actionAdded" o = Gio.ActionGroup.ActionGroupActionAddedMethodInfo
    ResolveApplicationMethod "actionEnabledChanged" o = Gio.ActionGroup.ActionGroupActionEnabledChangedMethodInfo
    ResolveApplicationMethod "actionRemoved" o = Gio.ActionGroup.ActionGroupActionRemovedMethodInfo
    ResolveApplicationMethod "actionStateChanged" o = Gio.ActionGroup.ActionGroupActionStateChangedMethodInfo
    ResolveApplicationMethod "activate" o = Gio.Application.ApplicationActivateMethodInfo
    ResolveApplicationMethod "activateAction" o = Gio.ActionGroup.ActionGroupActivateActionMethodInfo
    ResolveApplicationMethod "addAction" o = Gio.ActionMap.ActionMapAddActionMethodInfo
    ResolveApplicationMethod "addActionEntries" o = Gio.ActionMap.ActionMapAddActionEntriesMethodInfo
    ResolveApplicationMethod "addMainOption" o = Gio.Application.ApplicationAddMainOptionMethodInfo
    ResolveApplicationMethod "addMainOptionEntries" o = Gio.Application.ApplicationAddMainOptionEntriesMethodInfo
    ResolveApplicationMethod "addOptionGroup" o = Gio.Application.ApplicationAddOptionGroupMethodInfo
    ResolveApplicationMethod "addWindow" o = ApplicationAddWindowMethodInfo
    ResolveApplicationMethod "bindBusyProperty" o = Gio.Application.ApplicationBindBusyPropertyMethodInfo
    ResolveApplicationMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveApplicationMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveApplicationMethod "changeActionState" o = Gio.ActionGroup.ActionGroupChangeActionStateMethodInfo
    ResolveApplicationMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveApplicationMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveApplicationMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveApplicationMethod "hasAction" o = Gio.ActionGroup.ActionGroupHasActionMethodInfo
    ResolveApplicationMethod "hold" o = Gio.Application.ApplicationHoldMethodInfo
    ResolveApplicationMethod "inhibit" o = ApplicationInhibitMethodInfo
    ResolveApplicationMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveApplicationMethod "listActionDescriptions" o = ApplicationListActionDescriptionsMethodInfo
    ResolveApplicationMethod "listActions" o = Gio.ActionGroup.ActionGroupListActionsMethodInfo
    ResolveApplicationMethod "lookupAction" o = Gio.ActionMap.ActionMapLookupActionMethodInfo
    ResolveApplicationMethod "markBusy" o = Gio.Application.ApplicationMarkBusyMethodInfo
    ResolveApplicationMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveApplicationMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveApplicationMethod "open" o = Gio.Application.ApplicationOpenMethodInfo
    ResolveApplicationMethod "queryAction" o = Gio.ActionGroup.ActionGroupQueryActionMethodInfo
    ResolveApplicationMethod "quit" o = Gio.Application.ApplicationQuitMethodInfo
    ResolveApplicationMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveApplicationMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveApplicationMethod "register" o = Gio.Application.ApplicationRegisterMethodInfo
    ResolveApplicationMethod "release" o = Gio.Application.ApplicationReleaseMethodInfo
    ResolveApplicationMethod "removeAction" o = Gio.ActionMap.ActionMapRemoveActionMethodInfo
    ResolveApplicationMethod "removeActionEntries" o = Gio.ActionMap.ActionMapRemoveActionEntriesMethodInfo
    ResolveApplicationMethod "removeWindow" o = ApplicationRemoveWindowMethodInfo
    ResolveApplicationMethod "run" o = Gio.Application.ApplicationRunMethodInfo
    ResolveApplicationMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveApplicationMethod "sendNotification" o = Gio.Application.ApplicationSendNotificationMethodInfo
    ResolveApplicationMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveApplicationMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveApplicationMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveApplicationMethod "unbindBusyProperty" o = Gio.Application.ApplicationUnbindBusyPropertyMethodInfo
    ResolveApplicationMethod "uninhibit" o = ApplicationUninhibitMethodInfo
    ResolveApplicationMethod "unmarkBusy" o = Gio.Application.ApplicationUnmarkBusyMethodInfo
    ResolveApplicationMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveApplicationMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveApplicationMethod "withdrawNotification" o = Gio.Application.ApplicationWithdrawNotificationMethodInfo
    ResolveApplicationMethod "getAccelsForAction" o = ApplicationGetAccelsForActionMethodInfo
    ResolveApplicationMethod "getActionEnabled" o = Gio.ActionGroup.ActionGroupGetActionEnabledMethodInfo
    ResolveApplicationMethod "getActionParameterType" o = Gio.ActionGroup.ActionGroupGetActionParameterTypeMethodInfo
    ResolveApplicationMethod "getActionState" o = Gio.ActionGroup.ActionGroupGetActionStateMethodInfo
    ResolveApplicationMethod "getActionStateHint" o = Gio.ActionGroup.ActionGroupGetActionStateHintMethodInfo
    ResolveApplicationMethod "getActionStateType" o = Gio.ActionGroup.ActionGroupGetActionStateTypeMethodInfo
    ResolveApplicationMethod "getActionsForAccel" o = ApplicationGetActionsForAccelMethodInfo
    ResolveApplicationMethod "getActiveWindow" o = ApplicationGetActiveWindowMethodInfo
    ResolveApplicationMethod "getApplicationId" o = Gio.Application.ApplicationGetApplicationIdMethodInfo
    ResolveApplicationMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveApplicationMethod "getDbusConnection" o = Gio.Application.ApplicationGetDbusConnectionMethodInfo
    ResolveApplicationMethod "getDbusObjectPath" o = Gio.Application.ApplicationGetDbusObjectPathMethodInfo
    ResolveApplicationMethod "getFlags" o = Gio.Application.ApplicationGetFlagsMethodInfo
    ResolveApplicationMethod "getInactivityTimeout" o = Gio.Application.ApplicationGetInactivityTimeoutMethodInfo
    ResolveApplicationMethod "getIsBusy" o = Gio.Application.ApplicationGetIsBusyMethodInfo
    ResolveApplicationMethod "getIsRegistered" o = Gio.Application.ApplicationGetIsRegisteredMethodInfo
    ResolveApplicationMethod "getIsRemote" o = Gio.Application.ApplicationGetIsRemoteMethodInfo
    ResolveApplicationMethod "getMenuById" o = ApplicationGetMenuByIdMethodInfo
    ResolveApplicationMethod "getMenubar" o = ApplicationGetMenubarMethodInfo
    ResolveApplicationMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveApplicationMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveApplicationMethod "getResourceBasePath" o = Gio.Application.ApplicationGetResourceBasePathMethodInfo
    ResolveApplicationMethod "getVersion" o = Gio.Application.ApplicationGetVersionMethodInfo
    ResolveApplicationMethod "getWindowById" o = ApplicationGetWindowByIdMethodInfo
    ResolveApplicationMethod "getWindows" o = ApplicationGetWindowsMethodInfo
    ResolveApplicationMethod "setAccelsForAction" o = ApplicationSetAccelsForActionMethodInfo
    ResolveApplicationMethod "setActionGroup" o = Gio.Application.ApplicationSetActionGroupMethodInfo
    ResolveApplicationMethod "setApplicationId" o = Gio.Application.ApplicationSetApplicationIdMethodInfo
    ResolveApplicationMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveApplicationMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveApplicationMethod "setDefault" o = Gio.Application.ApplicationSetDefaultMethodInfo
    ResolveApplicationMethod "setFlags" o = Gio.Application.ApplicationSetFlagsMethodInfo
    ResolveApplicationMethod "setInactivityTimeout" o = Gio.Application.ApplicationSetInactivityTimeoutMethodInfo
    ResolveApplicationMethod "setMenubar" o = ApplicationSetMenubarMethodInfo
    ResolveApplicationMethod "setOptionContextDescription" o = Gio.Application.ApplicationSetOptionContextDescriptionMethodInfo
    ResolveApplicationMethod "setOptionContextParameterString" o = Gio.Application.ApplicationSetOptionContextParameterStringMethodInfo
    ResolveApplicationMethod "setOptionContextSummary" o = Gio.Application.ApplicationSetOptionContextSummaryMethodInfo
    ResolveApplicationMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveApplicationMethod "setResourceBasePath" o = Gio.Application.ApplicationSetResourceBasePathMethodInfo
    ResolveApplicationMethod "setVersion" o = Gio.Application.ApplicationSetVersionMethodInfo
    ResolveApplicationMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- signal Application::query-end
-- | Emitted when the session manager is about to end the session.
-- 
-- This signal is only emitted if [Application:registerSession]("GI.Gtk.Objects.Application#g:attr:registerSession")
-- is true. Applications can connect to this signal and call
-- 'GI.Gtk.Objects.Application.applicationInhibit' with [flags/@gtk@/.ApplicationInhibitFlags.logout]
-- to delay the end of the session until state has been saved.
type ApplicationQueryEndCallback =
    IO ()

type C_ApplicationQueryEndCallback =
    Ptr Application ->                      -- object
    Ptr () ->                               -- user_data
    IO ()

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

wrap_ApplicationQueryEndCallback :: 
    GObject a => (a -> ApplicationQueryEndCallback) ->
    C_ApplicationQueryEndCallback
wrap_ApplicationQueryEndCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_ApplicationQueryEndCallback
wrap_ApplicationQueryEndCallback a -> IO ()
gi'cb Ptr Application
gi'selfPtr Ptr ()
_ = do
    Ptr Application -> (Application -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr Application
gi'selfPtr ((Application -> IO ()) -> IO ())
-> (Application -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Application
gi'self -> a -> IO ()
gi'cb (Application -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Application
gi'self) 


-- | Connect a signal handler for the [queryEnd](#signal:queryEnd) 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' application #queryEnd callback
-- @
-- 
-- 
onApplicationQueryEnd :: (IsApplication a, MonadIO m) => a -> ((?self :: a) => ApplicationQueryEndCallback) -> m SignalHandlerId
onApplicationQueryEnd :: forall a (m :: * -> *).
(IsApplication a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onApplicationQueryEnd a
obj (?self::a) => IO ()
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 -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_ApplicationQueryEndCallback
wrapped' = (a -> IO ()) -> C_ApplicationQueryEndCallback
forall a.
GObject a =>
(a -> IO ()) -> C_ApplicationQueryEndCallback
wrap_ApplicationQueryEndCallback a -> IO ()
wrapped
    wrapped'' <- C_ApplicationQueryEndCallback
-> IO (FunPtr C_ApplicationQueryEndCallback)
mk_ApplicationQueryEndCallback C_ApplicationQueryEndCallback
wrapped'
    connectSignalFunPtr obj "query-end" wrapped'' SignalConnectBefore Nothing

-- | Connect a signal handler for the [queryEnd](#signal:queryEnd) 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' application #queryEnd 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.
-- 
afterApplicationQueryEnd :: (IsApplication a, MonadIO m) => a -> ((?self :: a) => ApplicationQueryEndCallback) -> m SignalHandlerId
afterApplicationQueryEnd :: forall a (m :: * -> *).
(IsApplication a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterApplicationQueryEnd a
obj (?self::a) => IO ()
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 -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_ApplicationQueryEndCallback
wrapped' = (a -> IO ()) -> C_ApplicationQueryEndCallback
forall a.
GObject a =>
(a -> IO ()) -> C_ApplicationQueryEndCallback
wrap_ApplicationQueryEndCallback a -> IO ()
wrapped
    wrapped'' <- C_ApplicationQueryEndCallback
-> IO (FunPtr C_ApplicationQueryEndCallback)
mk_ApplicationQueryEndCallback C_ApplicationQueryEndCallback
wrapped'
    connectSignalFunPtr obj "query-end" wrapped'' SignalConnectAfter Nothing


#if defined(ENABLE_OVERLOADING)
data ApplicationQueryEndSignalInfo
instance SignalInfo ApplicationQueryEndSignalInfo where
    type HaskellCallbackType ApplicationQueryEndSignalInfo = ApplicationQueryEndCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ApplicationQueryEndCallback cb
        cb'' <- mk_ApplicationQueryEndCallback cb'
        connectSignalFunPtr obj "query-end" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application::query-end"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#g:signal:queryEnd"})

#endif

-- signal Application::window-added
-- | Emitted when a window is added to an application.
-- 
-- See 'GI.Gtk.Objects.Application.applicationAddWindow'.
type ApplicationWindowAddedCallback =
    Gtk.Window.Window
    -- ^ /@window@/: the newly-added window
    -> IO ()

type C_ApplicationWindowAddedCallback =
    Ptr Application ->                      -- object
    Ptr Gtk.Window.Window ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_ApplicationWindowAddedCallback :: 
    GObject a => (a -> ApplicationWindowAddedCallback) ->
    C_ApplicationWindowAddedCallback
wrap_ApplicationWindowAddedCallback :: forall a.
GObject a =>
(a -> ApplicationWindowAddedCallback)
-> C_ApplicationWindowAddedCallback
wrap_ApplicationWindowAddedCallback a -> ApplicationWindowAddedCallback
gi'cb Ptr Application
gi'selfPtr Ptr Window
window Ptr ()
_ = do
    window' <- ((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
window
    B.ManagedPtr.withNewObject gi'selfPtr $ \Application
gi'self -> a -> ApplicationWindowAddedCallback
gi'cb (Application -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Application
gi'self)  Window
window'


-- | Connect a signal handler for the [windowAdded](#signal:windowAdded) 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' application #windowAdded callback
-- @
-- 
-- 
onApplicationWindowAdded :: (IsApplication a, MonadIO m) => a -> ((?self :: a) => ApplicationWindowAddedCallback) -> m SignalHandlerId
onApplicationWindowAdded :: forall a (m :: * -> *).
(IsApplication a, MonadIO m) =>
a
-> ((?self::a) => ApplicationWindowAddedCallback)
-> m SignalHandlerId
onApplicationWindowAdded a
obj (?self::a) => ApplicationWindowAddedCallback
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 -> ApplicationWindowAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => ApplicationWindowAddedCallback
ApplicationWindowAddedCallback
cb
    let wrapped' :: C_ApplicationWindowAddedCallback
wrapped' = (a -> ApplicationWindowAddedCallback)
-> C_ApplicationWindowAddedCallback
forall a.
GObject a =>
(a -> ApplicationWindowAddedCallback)
-> C_ApplicationWindowAddedCallback
wrap_ApplicationWindowAddedCallback a -> ApplicationWindowAddedCallback
wrapped
    wrapped'' <- C_ApplicationWindowAddedCallback
-> IO (FunPtr C_ApplicationWindowAddedCallback)
mk_ApplicationWindowAddedCallback C_ApplicationWindowAddedCallback
wrapped'
    connectSignalFunPtr obj "window-added" wrapped'' SignalConnectBefore Nothing

-- | Connect a signal handler for the [windowAdded](#signal:windowAdded) 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' application #windowAdded 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.
-- 
afterApplicationWindowAdded :: (IsApplication a, MonadIO m) => a -> ((?self :: a) => ApplicationWindowAddedCallback) -> m SignalHandlerId
afterApplicationWindowAdded :: forall a (m :: * -> *).
(IsApplication a, MonadIO m) =>
a
-> ((?self::a) => ApplicationWindowAddedCallback)
-> m SignalHandlerId
afterApplicationWindowAdded a
obj (?self::a) => ApplicationWindowAddedCallback
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 -> ApplicationWindowAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => ApplicationWindowAddedCallback
ApplicationWindowAddedCallback
cb
    let wrapped' :: C_ApplicationWindowAddedCallback
wrapped' = (a -> ApplicationWindowAddedCallback)
-> C_ApplicationWindowAddedCallback
forall a.
GObject a =>
(a -> ApplicationWindowAddedCallback)
-> C_ApplicationWindowAddedCallback
wrap_ApplicationWindowAddedCallback a -> ApplicationWindowAddedCallback
wrapped
    wrapped'' <- C_ApplicationWindowAddedCallback
-> IO (FunPtr C_ApplicationWindowAddedCallback)
mk_ApplicationWindowAddedCallback C_ApplicationWindowAddedCallback
wrapped'
    connectSignalFunPtr obj "window-added" wrapped'' SignalConnectAfter Nothing


#if defined(ENABLE_OVERLOADING)
data ApplicationWindowAddedSignalInfo
instance SignalInfo ApplicationWindowAddedSignalInfo where
    type HaskellCallbackType ApplicationWindowAddedSignalInfo = ApplicationWindowAddedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ApplicationWindowAddedCallback cb
        cb'' <- mk_ApplicationWindowAddedCallback cb'
        connectSignalFunPtr obj "window-added" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application::window-added"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#g:signal:windowAdded"})

#endif

-- signal Application::window-removed
-- | Emitted when a window is removed from an application.
-- 
-- This can happen as a side-effect of the window being destroyed
-- or explicitly through 'GI.Gtk.Objects.Application.applicationRemoveWindow'.
type ApplicationWindowRemovedCallback =
    Gtk.Window.Window
    -- ^ /@window@/: the window that is being removed
    -> IO ()

type C_ApplicationWindowRemovedCallback =
    Ptr Application ->                      -- object
    Ptr Gtk.Window.Window ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_ApplicationWindowRemovedCallback :: 
    GObject a => (a -> ApplicationWindowRemovedCallback) ->
    C_ApplicationWindowRemovedCallback
wrap_ApplicationWindowRemovedCallback :: forall a.
GObject a =>
(a -> ApplicationWindowAddedCallback)
-> C_ApplicationWindowAddedCallback
wrap_ApplicationWindowRemovedCallback a -> ApplicationWindowAddedCallback
gi'cb Ptr Application
gi'selfPtr Ptr Window
window Ptr ()
_ = do
    window' <- ((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
window
    B.ManagedPtr.withNewObject gi'selfPtr $ \Application
gi'self -> a -> ApplicationWindowAddedCallback
gi'cb (Application -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Application
gi'self)  Window
window'


-- | Connect a signal handler for the [windowRemoved](#signal:windowRemoved) 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' application #windowRemoved callback
-- @
-- 
-- 
onApplicationWindowRemoved :: (IsApplication a, MonadIO m) => a -> ((?self :: a) => ApplicationWindowRemovedCallback) -> m SignalHandlerId
onApplicationWindowRemoved :: forall a (m :: * -> *).
(IsApplication a, MonadIO m) =>
a
-> ((?self::a) => ApplicationWindowAddedCallback)
-> m SignalHandlerId
onApplicationWindowRemoved a
obj (?self::a) => ApplicationWindowAddedCallback
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 -> ApplicationWindowAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => ApplicationWindowAddedCallback
ApplicationWindowAddedCallback
cb
    let wrapped' :: C_ApplicationWindowAddedCallback
wrapped' = (a -> ApplicationWindowAddedCallback)
-> C_ApplicationWindowAddedCallback
forall a.
GObject a =>
(a -> ApplicationWindowAddedCallback)
-> C_ApplicationWindowAddedCallback
wrap_ApplicationWindowRemovedCallback a -> ApplicationWindowAddedCallback
wrapped
    wrapped'' <- C_ApplicationWindowAddedCallback
-> IO (FunPtr C_ApplicationWindowAddedCallback)
mk_ApplicationWindowRemovedCallback C_ApplicationWindowAddedCallback
wrapped'
    connectSignalFunPtr obj "window-removed" wrapped'' SignalConnectBefore Nothing

-- | Connect a signal handler for the [windowRemoved](#signal:windowRemoved) 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' application #windowRemoved 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.
-- 
afterApplicationWindowRemoved :: (IsApplication a, MonadIO m) => a -> ((?self :: a) => ApplicationWindowRemovedCallback) -> m SignalHandlerId
afterApplicationWindowRemoved :: forall a (m :: * -> *).
(IsApplication a, MonadIO m) =>
a
-> ((?self::a) => ApplicationWindowAddedCallback)
-> m SignalHandlerId
afterApplicationWindowRemoved a
obj (?self::a) => ApplicationWindowAddedCallback
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 -> ApplicationWindowAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => ApplicationWindowAddedCallback
ApplicationWindowAddedCallback
cb
    let wrapped' :: C_ApplicationWindowAddedCallback
wrapped' = (a -> ApplicationWindowAddedCallback)
-> C_ApplicationWindowAddedCallback
forall a.
GObject a =>
(a -> ApplicationWindowAddedCallback)
-> C_ApplicationWindowAddedCallback
wrap_ApplicationWindowRemovedCallback a -> ApplicationWindowAddedCallback
wrapped
    wrapped'' <- C_ApplicationWindowAddedCallback
-> IO (FunPtr C_ApplicationWindowAddedCallback)
mk_ApplicationWindowRemovedCallback C_ApplicationWindowAddedCallback
wrapped'
    connectSignalFunPtr obj "window-removed" wrapped'' SignalConnectAfter Nothing


#if defined(ENABLE_OVERLOADING)
data ApplicationWindowRemovedSignalInfo
instance SignalInfo ApplicationWindowRemovedSignalInfo where
    type HaskellCallbackType ApplicationWindowRemovedSignalInfo = ApplicationWindowRemovedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ApplicationWindowRemovedCallback cb
        cb'' <- mk_ApplicationWindowRemovedCallback cb'
        connectSignalFunPtr obj "window-removed" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application::window-removed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#g:signal:windowRemoved"})

#endif

-- VVV Prop "active-window"
   -- Type: TInterface (Name {namespace = "Gtk", name = "Window"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@active-window@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' application #activeWindow
-- @
getApplicationActiveWindow :: (MonadIO m, IsApplication o) => o -> m (Maybe Gtk.Window.Window)
getApplicationActiveWindow :: forall (m :: * -> *) o.
(MonadIO m, IsApplication o) =>
o -> m (Maybe Window)
getApplicationActiveWindow 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
"active-window" ManagedPtr Window -> Window
Gtk.Window.Window

#if defined(ENABLE_OVERLOADING)
data ApplicationActiveWindowPropertyInfo
instance AttrInfo ApplicationActiveWindowPropertyInfo where
    type AttrAllowedOps ApplicationActiveWindowPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ApplicationActiveWindowPropertyInfo = IsApplication
    type AttrSetTypeConstraint ApplicationActiveWindowPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ApplicationActiveWindowPropertyInfo = (~) ()
    type AttrTransferType ApplicationActiveWindowPropertyInfo = ()
    type AttrGetType ApplicationActiveWindowPropertyInfo = (Maybe Gtk.Window.Window)
    type AttrLabel ApplicationActiveWindowPropertyInfo = "active-window"
    type AttrOrigin ApplicationActiveWindowPropertyInfo = Application
    attrGet = getApplicationActiveWindow
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.activeWindow"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#g:attr:activeWindow"
        })
#endif

-- VVV Prop "menubar"
   -- Type: TInterface (Name {namespace = "Gio", name = "MenuModel"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

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

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

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

-- | Set the value of the “@menubar@” 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' #menubar
-- @
clearApplicationMenubar :: (MonadIO m, IsApplication o) => o -> m ()
clearApplicationMenubar :: forall (m :: * -> *) o. (MonadIO m, IsApplication o) => o -> m ()
clearApplicationMenubar 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 MenuModel -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"menubar" (Maybe MenuModel
forall a. Maybe a
Nothing :: Maybe Gio.MenuModel.MenuModel)

#if defined(ENABLE_OVERLOADING)
data ApplicationMenubarPropertyInfo
instance AttrInfo ApplicationMenubarPropertyInfo where
    type AttrAllowedOps ApplicationMenubarPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ApplicationMenubarPropertyInfo = IsApplication
    type AttrSetTypeConstraint ApplicationMenubarPropertyInfo = Gio.MenuModel.IsMenuModel
    type AttrTransferTypeConstraint ApplicationMenubarPropertyInfo = Gio.MenuModel.IsMenuModel
    type AttrTransferType ApplicationMenubarPropertyInfo = Gio.MenuModel.MenuModel
    type AttrGetType ApplicationMenubarPropertyInfo = (Maybe Gio.MenuModel.MenuModel)
    type AttrLabel ApplicationMenubarPropertyInfo = "menubar"
    type AttrOrigin ApplicationMenubarPropertyInfo = Application
    attrGet = getApplicationMenubar
    attrSet = setApplicationMenubar
    attrTransfer _ v = do
        unsafeCastTo Gio.MenuModel.MenuModel v
    attrConstruct = constructApplicationMenubar
    attrClear = clearApplicationMenubar
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.menubar"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#g:attr:menubar"
        })
#endif

-- VVV Prop "register-session"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

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

#if defined(ENABLE_OVERLOADING)
data ApplicationRegisterSessionPropertyInfo
instance AttrInfo ApplicationRegisterSessionPropertyInfo where
    type AttrAllowedOps ApplicationRegisterSessionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ApplicationRegisterSessionPropertyInfo = IsApplication
    type AttrSetTypeConstraint ApplicationRegisterSessionPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint ApplicationRegisterSessionPropertyInfo = (~) Bool
    type AttrTransferType ApplicationRegisterSessionPropertyInfo = Bool
    type AttrGetType ApplicationRegisterSessionPropertyInfo = Bool
    type AttrLabel ApplicationRegisterSessionPropertyInfo = "register-session"
    type AttrOrigin ApplicationRegisterSessionPropertyInfo = Application
    attrGet = getApplicationRegisterSession
    attrSet = setApplicationRegisterSession
    attrTransfer _ v = do
        return v
    attrConstruct = constructApplicationRegisterSession
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.registerSession"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#g:attr:registerSession"
        })
#endif

-- VVV Prop "screensaver-active"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data ApplicationScreensaverActivePropertyInfo
instance AttrInfo ApplicationScreensaverActivePropertyInfo where
    type AttrAllowedOps ApplicationScreensaverActivePropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint ApplicationScreensaverActivePropertyInfo = IsApplication
    type AttrSetTypeConstraint ApplicationScreensaverActivePropertyInfo = (~) ()
    type AttrTransferTypeConstraint ApplicationScreensaverActivePropertyInfo = (~) ()
    type AttrTransferType ApplicationScreensaverActivePropertyInfo = ()
    type AttrGetType ApplicationScreensaverActivePropertyInfo = Bool
    type AttrLabel ApplicationScreensaverActivePropertyInfo = "screensaver-active"
    type AttrOrigin ApplicationScreensaverActivePropertyInfo = Application
    attrGet = getApplicationScreensaverActive
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.screensaverActive"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#g:attr:screensaverActive"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Application
type instance O.AttributeList Application = ApplicationAttributeList
type ApplicationAttributeList = ('[ '("actionGroup", Gio.Application.ApplicationActionGroupPropertyInfo), '("activeWindow", ApplicationActiveWindowPropertyInfo), '("applicationId", Gio.Application.ApplicationApplicationIdPropertyInfo), '("flags", Gio.Application.ApplicationFlagsPropertyInfo), '("inactivityTimeout", Gio.Application.ApplicationInactivityTimeoutPropertyInfo), '("isBusy", Gio.Application.ApplicationIsBusyPropertyInfo), '("isRegistered", Gio.Application.ApplicationIsRegisteredPropertyInfo), '("isRemote", Gio.Application.ApplicationIsRemotePropertyInfo), '("menubar", ApplicationMenubarPropertyInfo), '("registerSession", ApplicationRegisterSessionPropertyInfo), '("resourceBasePath", Gio.Application.ApplicationResourceBasePathPropertyInfo), '("screensaverActive", ApplicationScreensaverActivePropertyInfo), '("version", Gio.Application.ApplicationVersionPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
applicationActiveWindow :: AttrLabelProxy "activeWindow"
applicationActiveWindow = AttrLabelProxy

applicationMenubar :: AttrLabelProxy "menubar"
applicationMenubar = AttrLabelProxy

applicationRegisterSession :: AttrLabelProxy "registerSession"
applicationRegisterSession = AttrLabelProxy

applicationScreensaverActive :: AttrLabelProxy "screensaverActive"
applicationScreensaverActive = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Application = ApplicationSignalList
type ApplicationSignalList = ('[ '("actionAdded", Gio.ActionGroup.ActionGroupActionAddedSignalInfo), '("actionEnabledChanged", Gio.ActionGroup.ActionGroupActionEnabledChangedSignalInfo), '("actionRemoved", Gio.ActionGroup.ActionGroupActionRemovedSignalInfo), '("actionStateChanged", Gio.ActionGroup.ActionGroupActionStateChangedSignalInfo), '("activate", Gio.Application.ApplicationActivateSignalInfo), '("commandLine", Gio.Application.ApplicationCommandLineSignalInfo), '("handleLocalOptions", Gio.Application.ApplicationHandleLocalOptionsSignalInfo), '("nameLost", Gio.Application.ApplicationNameLostSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("open", Gio.Application.ApplicationOpenSignalInfo), '("queryEnd", ApplicationQueryEndSignalInfo), '("shutdown", Gio.Application.ApplicationShutdownSignalInfo), '("startup", Gio.Application.ApplicationStartupSignalInfo), '("windowAdded", ApplicationWindowAddedSignalInfo), '("windowRemoved", ApplicationWindowRemovedSignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method Application::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "application_id"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The application ID" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ApplicationFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the application flags"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Application" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_application_new" gtk_application_new :: 
    CString ->                              -- application_id : TBasicType TUTF8
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "ApplicationFlags"})
    IO (Ptr Application)

-- | Creates a new application instance.
-- 
-- When using @GtkApplication@, it is not necessary to call 'GI.Gtk.Functions.init'
-- manually. It is called as soon as the application gets registered as
-- the primary instance.
-- 
-- Concretely, 'GI.Gtk.Functions.init' is called in the default handler for the
-- @GApplication::startup@ signal. Therefore, @GtkApplication@ subclasses
-- should always chain up in their @/GIO.Application.startup()/@ handler
-- before using any GTK API.
-- 
-- Note that commandline arguments are not passed to 'GI.Gtk.Functions.init'.
-- 
-- If @application_id@ is not @NULL@, then it must be valid. See
-- 'GI.Gio.Objects.Application.applicationIdIsValid'.
-- 
-- If no application ID is given then some features (most notably application
-- uniqueness) will be disabled.
applicationNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (T.Text)
    -- ^ /@applicationId@/: The application ID
    -> [Gio.Flags.ApplicationFlags]
    -- ^ /@flags@/: the application flags
    -> m Application
    -- ^ __Returns:__ a new @GtkApplication@ instance
applicationNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe Text -> [ApplicationFlags] -> m Application
applicationNew Maybe Text
applicationId [ApplicationFlags]
flags = IO Application -> m Application
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Application -> m Application)
-> IO Application -> m Application
forall a b. (a -> b) -> a -> b
$ do
    maybeApplicationId <- case Maybe Text
applicationId of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
        Just Text
jApplicationId -> do
            jApplicationId' <- Text -> IO (Ptr CChar)
textToCString Text
jApplicationId
            return jApplicationId'
    let flags' = [ApplicationFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ApplicationFlags]
flags
    result <- gtk_application_new maybeApplicationId flags'
    checkUnexpectedReturnNULL "applicationNew" result
    result' <- (wrapObject Application) result
    freeMem maybeApplicationId
    return result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Application::add_window
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "application"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Application" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an application" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "window"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a window" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_application_add_window" gtk_application_add_window :: 
    Ptr Application ->                      -- application : TInterface (Name {namespace = "Gtk", name = "Application"})
    Ptr Gtk.Window.Window ->                -- window : TInterface (Name {namespace = "Gtk", name = "Window"})
    IO ()

-- | Adds a window to the application.
-- 
-- This call can only happen after the application has started;
-- typically, you should add new application windows in response
-- to the emission of the @/GIO.Application::activate/@ signal.
-- 
-- This call is equivalent to setting the [Window:application]("GI.Gtk.Objects.Window#g:attr:application")
-- property of the window to /@application@/.
-- 
-- Normally, the connection between the application and the window
-- will remain until the window is destroyed, but you can explicitly
-- remove it with 'GI.Gtk.Objects.Application.applicationRemoveWindow'.
-- 
-- GTK will keep the application running as long as it has any windows.
applicationAddWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsApplication a, Gtk.Window.IsWindow b) =>
    a
    -- ^ /@application@/: an application
    -> b
    -- ^ /@window@/: a window
    -> m ()
applicationAddWindow :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsApplication a, IsWindow b) =>
a -> b -> m ()
applicationAddWindow a
application b
window = 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
    application' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
application
    window' <- unsafeManagedPtrCastPtr window
    gtk_application_add_window application' window'
    touchManagedPtr application
    touchManagedPtr window
    return ()

#if defined(ENABLE_OVERLOADING)
data ApplicationAddWindowMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsApplication a, Gtk.Window.IsWindow b) => O.OverloadedMethod ApplicationAddWindowMethodInfo a signature where
    overloadedMethod = applicationAddWindow

instance O.OverloadedMethodInfo ApplicationAddWindowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.applicationAddWindow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#v:applicationAddWindow"
        })


#endif

-- method Application::get_accels_for_action
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "application"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Application" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an application" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "detailed_action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a detailed action name, specifying an action\n  and target to obtain accelerators for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_application_get_accels_for_action" gtk_application_get_accels_for_action :: 
    Ptr Application ->                      -- application : TInterface (Name {namespace = "Gtk", name = "Application"})
    CString ->                              -- detailed_action_name : TBasicType TUTF8
    IO (Ptr CString)

-- | Gets the accelerators that are currently associated with
-- the given action.
applicationGetAccelsForAction ::
    (B.CallStack.HasCallStack, MonadIO m, IsApplication a) =>
    a
    -- ^ /@application@/: an application
    -> T.Text
    -- ^ /@detailedActionName@/: a detailed action name, specifying an action
    --   and target to obtain accelerators for
    -> m [T.Text]
    -- ^ __Returns:__ 
    --   accelerators for /@detailedActionName@/
applicationGetAccelsForAction :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsApplication a) =>
a -> Text -> m [Text]
applicationGetAccelsForAction a
application Text
detailedActionName = IO [Text] -> m [Text]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
    application' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
application
    detailedActionName' <- textToCString detailedActionName
    result <- gtk_application_get_accels_for_action application' detailedActionName'
    checkUnexpectedReturnNULL "applicationGetAccelsForAction" result
    result' <- unpackZeroTerminatedUTF8CArray result
    mapZeroTerminatedCArray freeMem result
    freeMem result
    touchManagedPtr application
    freeMem detailedActionName'
    return result'

#if defined(ENABLE_OVERLOADING)
data ApplicationGetAccelsForActionMethodInfo
instance (signature ~ (T.Text -> m [T.Text]), MonadIO m, IsApplication a) => O.OverloadedMethod ApplicationGetAccelsForActionMethodInfo a signature where
    overloadedMethod = applicationGetAccelsForAction

instance O.OverloadedMethodInfo ApplicationGetAccelsForActionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.applicationGetAccelsForAction",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#v:applicationGetAccelsForAction"
        })


#endif

-- method Application::get_actions_for_accel
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "application"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Application" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a application" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "accel"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an accelerator that can be parsed by [func@Gtk.accelerator_parse]"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_application_get_actions_for_accel" gtk_application_get_actions_for_accel :: 
    Ptr Application ->                      -- application : TInterface (Name {namespace = "Gtk", name = "Application"})
    CString ->                              -- accel : TBasicType TUTF8
    IO (Ptr CString)

-- | Returns the list of actions (possibly empty) that the accelerator maps to.
-- 
-- Each item in the list is a detailed action name in the usual form.
-- 
-- This might be useful to discover if an accel already exists in
-- order to prevent installation of a conflicting accelerator (from
-- an accelerator editor or a plugin system, for example). Note that
-- having more than one action per accelerator may not be a bad thing
-- and might make sense in cases where the actions never appear in the
-- same context.
-- 
-- In case there are no actions for a given accelerator, an empty array
-- is returned. @NULL@ is never returned.
-- 
-- It is a programmer error to pass an invalid accelerator string.
-- 
-- If you are unsure, check it with 'GI.Gtk.Functions.acceleratorParse' first.
applicationGetActionsForAccel ::
    (B.CallStack.HasCallStack, MonadIO m, IsApplication a) =>
    a
    -- ^ /@application@/: a application
    -> T.Text
    -- ^ /@accel@/: an accelerator that can be parsed by 'GI.Gtk.Functions.acceleratorParse'
    -> m [T.Text]
    -- ^ __Returns:__ actions for /@accel@/
applicationGetActionsForAccel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsApplication a) =>
a -> Text -> m [Text]
applicationGetActionsForAccel a
application Text
accel = IO [Text] -> m [Text]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
    application' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
application
    accel' <- textToCString accel
    result <- gtk_application_get_actions_for_accel application' accel'
    checkUnexpectedReturnNULL "applicationGetActionsForAccel" result
    result' <- unpackZeroTerminatedUTF8CArray result
    mapZeroTerminatedCArray freeMem result
    freeMem result
    touchManagedPtr application
    freeMem accel'
    return result'

#if defined(ENABLE_OVERLOADING)
data ApplicationGetActionsForAccelMethodInfo
instance (signature ~ (T.Text -> m [T.Text]), MonadIO m, IsApplication a) => O.OverloadedMethod ApplicationGetActionsForAccelMethodInfo a signature where
    overloadedMethod = applicationGetActionsForAccel

instance O.OverloadedMethodInfo ApplicationGetActionsForAccelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.applicationGetActionsForAccel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#v:applicationGetActionsForAccel"
        })


#endif

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

foreign import ccall "gtk_application_get_active_window" gtk_application_get_active_window :: 
    Ptr Application ->                      -- application : TInterface (Name {namespace = "Gtk", name = "Application"})
    IO (Ptr Gtk.Window.Window)

-- | Gets the “active” window for the application.
-- 
-- The active window is the one that was most recently focused
-- (within the application). This window may not have the focus
-- at the moment if another application has it — this is just
-- the most recently-focused window within this application.
applicationGetActiveWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsApplication a) =>
    a
    -- ^ /@application@/: an application
    -> m (Maybe Gtk.Window.Window)
    -- ^ __Returns:__ the active window
applicationGetActiveWindow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsApplication a) =>
a -> m (Maybe Window)
applicationGetActiveWindow a
application = 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
    application' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
application
    result <- gtk_application_get_active_window application'
    maybeResult <- convertIfNonNull result $ \Ptr Window
result' -> do
        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'
        return result''
    touchManagedPtr application
    return maybeResult

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

instance O.OverloadedMethodInfo ApplicationGetActiveWindowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.applicationGetActiveWindow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#v:applicationGetActiveWindow"
        })


#endif

-- method Application::get_menu_by_id
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "application"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Application" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an application" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "id"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the ID of the menu to look up"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Menu" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_application_get_menu_by_id" gtk_application_get_menu_by_id :: 
    Ptr Application ->                      -- application : TInterface (Name {namespace = "Gtk", name = "Application"})
    CString ->                              -- id : TBasicType TUTF8
    IO (Ptr Gio.Menu.Menu)

-- | Gets a menu from automatically loaded resources.
-- 
-- See <https://docs.gtk.org/gtk4/class.Application.html#automatic-resources the section on Automatic resources>
-- for more information.
applicationGetMenuById ::
    (B.CallStack.HasCallStack, MonadIO m, IsApplication a) =>
    a
    -- ^ /@application@/: an application
    -> T.Text
    -- ^ /@id@/: the ID of the menu to look up
    -> m (Maybe Gio.Menu.Menu)
    -- ^ __Returns:__ Gets the menu with the
    --   given ID from the automatically loaded resources
applicationGetMenuById :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsApplication a) =>
a -> Text -> m (Maybe Menu)
applicationGetMenuById a
application Text
id = IO (Maybe Menu) -> m (Maybe Menu)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Menu) -> m (Maybe Menu))
-> IO (Maybe Menu) -> m (Maybe Menu)
forall a b. (a -> b) -> a -> b
$ do
    application' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
application
    id' <- textToCString id
    result <- gtk_application_get_menu_by_id application' id'
    maybeResult <- convertIfNonNull result $ \Ptr Menu
result' -> do
        result'' <- ((ManagedPtr Menu -> Menu) -> Ptr Menu -> IO Menu
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Menu -> Menu
Gio.Menu.Menu) Ptr Menu
result'
        return result''
    touchManagedPtr application
    freeMem id'
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data ApplicationGetMenuByIdMethodInfo
instance (signature ~ (T.Text -> m (Maybe Gio.Menu.Menu)), MonadIO m, IsApplication a) => O.OverloadedMethod ApplicationGetMenuByIdMethodInfo a signature where
    overloadedMethod = applicationGetMenuById

instance O.OverloadedMethodInfo ApplicationGetMenuByIdMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.applicationGetMenuById",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#v:applicationGetMenuById"
        })


#endif

-- method Application::get_menubar
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "application"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Application" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an application" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "MenuModel" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_application_get_menubar" gtk_application_get_menubar :: 
    Ptr Application ->                      -- application : TInterface (Name {namespace = "Gtk", name = "Application"})
    IO (Ptr Gio.MenuModel.MenuModel)

-- | Returns the menu model for the menu bar of the application.
applicationGetMenubar ::
    (B.CallStack.HasCallStack, MonadIO m, IsApplication a) =>
    a
    -- ^ /@application@/: an application
    -> m (Maybe Gio.MenuModel.MenuModel)
    -- ^ __Returns:__ the menubar for windows of the application
applicationGetMenubar :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsApplication a) =>
a -> m (Maybe MenuModel)
applicationGetMenubar a
application = IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe MenuModel) -> m (Maybe MenuModel))
-> IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall a b. (a -> b) -> a -> b
$ do
    application' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
application
    result <- gtk_application_get_menubar application'
    maybeResult <- convertIfNonNull result $ \Ptr MenuModel
result' -> do
        result'' <- ((ManagedPtr MenuModel -> MenuModel)
-> Ptr MenuModel -> IO MenuModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr MenuModel -> MenuModel
Gio.MenuModel.MenuModel) Ptr MenuModel
result'
        return result''
    touchManagedPtr application
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data ApplicationGetMenubarMethodInfo
instance (signature ~ (m (Maybe Gio.MenuModel.MenuModel)), MonadIO m, IsApplication a) => O.OverloadedMethod ApplicationGetMenubarMethodInfo a signature where
    overloadedMethod = applicationGetMenubar

instance O.OverloadedMethodInfo ApplicationGetMenubarMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.applicationGetMenubar",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#v:applicationGetMenubar"
        })


#endif

-- method Application::get_window_by_id
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "application"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Application" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an application`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "id"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an identifier number"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Window" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_application_get_window_by_id" gtk_application_get_window_by_id :: 
    Ptr Application ->                      -- application : TInterface (Name {namespace = "Gtk", name = "Application"})
    Word32 ->                               -- id : TBasicType TUInt
    IO (Ptr Gtk.Window.Window)

-- | Returns the window with the given ID.
-- 
-- The ID of a @GtkApplicationWindow@ can be retrieved with
-- 'GI.Gtk.Objects.ApplicationWindow.applicationWindowGetId'.
applicationGetWindowById ::
    (B.CallStack.HasCallStack, MonadIO m, IsApplication a) =>
    a
    -- ^ /@application@/: an application\`
    -> Word32
    -- ^ /@id@/: an identifier number
    -> m (Maybe Gtk.Window.Window)
    -- ^ __Returns:__ the window for the given ID
applicationGetWindowById :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsApplication a) =>
a -> Word32 -> m (Maybe Window)
applicationGetWindowById a
application Word32
id = 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
    application' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
application
    result <- gtk_application_get_window_by_id application' id
    maybeResult <- convertIfNonNull result $ \Ptr Window
result' -> do
        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'
        return result''
    touchManagedPtr application
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data ApplicationGetWindowByIdMethodInfo
instance (signature ~ (Word32 -> m (Maybe Gtk.Window.Window)), MonadIO m, IsApplication a) => O.OverloadedMethod ApplicationGetWindowByIdMethodInfo a signature where
    overloadedMethod = applicationGetWindowById

instance O.OverloadedMethodInfo ApplicationGetWindowByIdMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.applicationGetWindowById",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#v:applicationGetWindowById"
        })


#endif

-- method Application::get_windows
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "application"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Application" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an application" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList (TInterface Name { namespace = "Gtk" , name = "Window" }))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_application_get_windows" gtk_application_get_windows :: 
    Ptr Application ->                      -- application : TInterface (Name {namespace = "Gtk", name = "Application"})
    IO (Ptr (GList (Ptr Gtk.Window.Window)))

-- | Gets a list of the window associated with the application.
-- 
-- The list is sorted by most recently focused window, such that the first
-- element is the currently focused window. (Useful for choosing a parent
-- for a transient window.)
-- 
-- The list that is returned should not be modified in any way. It will
-- only remain valid until the next focus change or window creation or
-- deletion.
applicationGetWindows ::
    (B.CallStack.HasCallStack, MonadIO m, IsApplication a) =>
    a
    -- ^ /@application@/: an application
    -> m [Gtk.Window.Window]
    -- ^ __Returns:__ the list of windows
applicationGetWindows :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsApplication a) =>
a -> m [Window]
applicationGetWindows a
application = IO [Window] -> m [Window]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Window] -> m [Window]) -> IO [Window] -> m [Window]
forall a b. (a -> b) -> a -> b
$ do
    application' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
application
    result <- gtk_application_get_windows application'
    result' <- unpackGList result
    result'' <- mapM (newObject Gtk.Window.Window) result'
    touchManagedPtr application
    return result''

#if defined(ENABLE_OVERLOADING)
data ApplicationGetWindowsMethodInfo
instance (signature ~ (m [Gtk.Window.Window]), MonadIO m, IsApplication a) => O.OverloadedMethod ApplicationGetWindowsMethodInfo a signature where
    overloadedMethod = applicationGetWindows

instance O.OverloadedMethodInfo ApplicationGetWindowsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.applicationGetWindows",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#v:applicationGetWindows"
        })


#endif

-- method Application::inhibit
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "application"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Application" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the application" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "window"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a window" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "ApplicationInhibitFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "what types of actions should be inhibited"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "reason"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a short, human-readable string that explains\n  why these operations are inhibited"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_application_inhibit" gtk_application_inhibit :: 
    Ptr Application ->                      -- application : TInterface (Name {namespace = "Gtk", name = "Application"})
    Ptr Gtk.Window.Window ->                -- window : TInterface (Name {namespace = "Gtk", name = "Window"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gtk", name = "ApplicationInhibitFlags"})
    CString ->                              -- reason : TBasicType TUTF8
    IO Word32

-- | Informs the session manager that certain types of actions should be
-- inhibited.
-- 
-- This is not guaranteed to work on all platforms and for all types of
-- actions.
-- 
-- Applications should invoke this method when they begin an operation
-- that should not be interrupted, such as creating a CD or DVD. The
-- types of actions that may be blocked are specified by the /@flags@/
-- parameter. When the application completes the operation it should
-- call 'GI.Gtk.Objects.Application.applicationUninhibit' to remove the inhibitor. Note
-- that an application can have multiple inhibitors, and all of them must
-- be individually removed. Inhibitors are also cleared when the
-- application exits.
-- 
-- Applications should not expect that they will always be able to block
-- the action. In most cases, users will be given the option to force
-- the action to take place.
-- 
-- The /@reason@/ message should be short and to the point.
-- 
-- If a window is given, the session manager may point the user to
-- this window to find out more about why the action is inhibited.
-- 
-- The cookie that is returned by this function  should be used as an
-- argument to 'GI.Gtk.Objects.Application.applicationUninhibit' in order to remove
-- the request.
applicationInhibit ::
    (B.CallStack.HasCallStack, MonadIO m, IsApplication a, Gtk.Window.IsWindow b) =>
    a
    -- ^ /@application@/: the application
    -> Maybe (b)
    -- ^ /@window@/: a window
    -> [Gtk.Flags.ApplicationInhibitFlags]
    -- ^ /@flags@/: what types of actions should be inhibited
    -> Maybe (T.Text)
    -- ^ /@reason@/: a short, human-readable string that explains
    --   why these operations are inhibited
    -> m Word32
    -- ^ __Returns:__ A non-zero cookie that is used to uniquely identify this, or
    --   0 if the platform does not support inhibiting or the request failed
    --   for some reason
applicationInhibit :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsApplication a, IsWindow b) =>
a -> Maybe b -> [ApplicationInhibitFlags] -> Maybe Text -> m Word32
applicationInhibit a
application Maybe b
window [ApplicationInhibitFlags]
flags Maybe Text
reason = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    application' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
application
    maybeWindow <- case window 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
FP.nullPtr
        Just b
jWindow -> do
            jWindow' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jWindow
            return jWindow'
    let flags' = [ApplicationInhibitFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ApplicationInhibitFlags]
flags
    maybeReason <- case reason of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
        Just Text
jReason -> do
            jReason' <- Text -> IO (Ptr CChar)
textToCString Text
jReason
            return jReason'
    result <- gtk_application_inhibit application' maybeWindow flags' maybeReason
    touchManagedPtr application
    whenJust window touchManagedPtr
    freeMem maybeReason
    return result

#if defined(ENABLE_OVERLOADING)
data ApplicationInhibitMethodInfo
instance (signature ~ (Maybe (b) -> [Gtk.Flags.ApplicationInhibitFlags] -> Maybe (T.Text) -> m Word32), MonadIO m, IsApplication a, Gtk.Window.IsWindow b) => O.OverloadedMethod ApplicationInhibitMethodInfo a signature where
    overloadedMethod = applicationInhibit

instance O.OverloadedMethodInfo ApplicationInhibitMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.applicationInhibit",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#v:applicationInhibit"
        })


#endif

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

foreign import ccall "gtk_application_list_action_descriptions" gtk_application_list_action_descriptions :: 
    Ptr Application ->                      -- application : TInterface (Name {namespace = "Gtk", name = "Application"})
    IO (Ptr CString)

-- | Lists the detailed action names which have associated accelerators.
-- 
-- See 'GI.Gtk.Objects.Application.applicationSetAccelsForAction'.
applicationListActionDescriptions ::
    (B.CallStack.HasCallStack, MonadIO m, IsApplication a) =>
    a
    -- ^ /@application@/: an application
    -> m [T.Text]
    -- ^ __Returns:__ the detailed action names
applicationListActionDescriptions :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsApplication a) =>
a -> m [Text]
applicationListActionDescriptions a
application = IO [Text] -> m [Text]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
    application' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
application
    result <- gtk_application_list_action_descriptions application'
    checkUnexpectedReturnNULL "applicationListActionDescriptions" result
    result' <- unpackZeroTerminatedUTF8CArray result
    mapZeroTerminatedCArray freeMem result
    freeMem result
    touchManagedPtr application
    return result'

#if defined(ENABLE_OVERLOADING)
data ApplicationListActionDescriptionsMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsApplication a) => O.OverloadedMethod ApplicationListActionDescriptionsMethodInfo a signature where
    overloadedMethod = applicationListActionDescriptions

instance O.OverloadedMethodInfo ApplicationListActionDescriptionsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.applicationListActionDescriptions",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#v:applicationListActionDescriptions"
        })


#endif

-- method Application::remove_window
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "application"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Application" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an application" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "window"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a window" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_application_remove_window" gtk_application_remove_window :: 
    Ptr Application ->                      -- application : TInterface (Name {namespace = "Gtk", name = "Application"})
    Ptr Gtk.Window.Window ->                -- window : TInterface (Name {namespace = "Gtk", name = "Window"})
    IO ()

-- | Remove a window from the application.
-- 
-- If the window belongs to the application then this call is
-- equivalent to setting the [Window:application]("GI.Gtk.Objects.Window#g:attr:application")
-- property of the window to @NULL@.
-- 
-- The application may stop running as a result of a call to this
-- function, if the window was the last window of the application.
applicationRemoveWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsApplication a, Gtk.Window.IsWindow b) =>
    a
    -- ^ /@application@/: an application
    -> b
    -- ^ /@window@/: a window
    -> m ()
applicationRemoveWindow :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsApplication a, IsWindow b) =>
a -> b -> m ()
applicationRemoveWindow a
application b
window = 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
    application' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
application
    window' <- unsafeManagedPtrCastPtr window
    gtk_application_remove_window application' window'
    touchManagedPtr application
    touchManagedPtr window
    return ()

#if defined(ENABLE_OVERLOADING)
data ApplicationRemoveWindowMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsApplication a, Gtk.Window.IsWindow b) => O.OverloadedMethod ApplicationRemoveWindowMethodInfo a signature where
    overloadedMethod = applicationRemoveWindow

instance O.OverloadedMethodInfo ApplicationRemoveWindowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.applicationRemoveWindow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#v:applicationRemoveWindow"
        })


#endif

-- method Application::set_accels_for_action
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "application"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Application" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an application" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "detailed_action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a detailed action name, specifying an action\n  and target to associate accelerators with"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "accels"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a list of accelerators in the format\n  understood by [func@Gtk.accelerator_parse]"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_application_set_accels_for_action" gtk_application_set_accels_for_action :: 
    Ptr Application ->                      -- application : TInterface (Name {namespace = "Gtk", name = "Application"})
    CString ->                              -- detailed_action_name : TBasicType TUTF8
    Ptr CString ->                          -- accels : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO ()

-- | Sets zero or more keyboard accelerators that will trigger the
-- given action.
-- 
-- The first item in /@accels@/ will be the primary accelerator,
-- which may be displayed in the UI.
-- 
-- To remove all accelerators for an action, use an empty,
-- zero-terminated array for /@accels@/.
-- 
-- For the /@detailedActionName@/, see 'GI.Gio.Interfaces.Action.actionParseDetailedName'
-- and [Gio.Action.print_detailed_name].
applicationSetAccelsForAction ::
    (B.CallStack.HasCallStack, MonadIO m, IsApplication a) =>
    a
    -- ^ /@application@/: an application
    -> T.Text
    -- ^ /@detailedActionName@/: a detailed action name, specifying an action
    --   and target to associate accelerators with
    -> [T.Text]
    -- ^ /@accels@/: a list of accelerators in the format
    --   understood by 'GI.Gtk.Functions.acceleratorParse'
    -> m ()
applicationSetAccelsForAction :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsApplication a) =>
a -> Text -> [Text] -> m ()
applicationSetAccelsForAction a
application Text
detailedActionName [Text]
accels = 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
    application' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
application
    detailedActionName' <- textToCString detailedActionName
    accels' <- packZeroTerminatedUTF8CArray accels
    gtk_application_set_accels_for_action application' detailedActionName' accels'
    touchManagedPtr application
    freeMem detailedActionName'
    mapZeroTerminatedCArray freeMem accels'
    freeMem accels'
    return ()

#if defined(ENABLE_OVERLOADING)
data ApplicationSetAccelsForActionMethodInfo
instance (signature ~ (T.Text -> [T.Text] -> m ()), MonadIO m, IsApplication a) => O.OverloadedMethod ApplicationSetAccelsForActionMethodInfo a signature where
    overloadedMethod = applicationSetAccelsForAction

instance O.OverloadedMethodInfo ApplicationSetAccelsForActionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.applicationSetAccelsForAction",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#v:applicationSetAccelsForAction"
        })


#endif

-- method Application::set_menubar
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "application"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Application" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an application" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "menubar"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuModel" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a menu model" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_application_set_menubar" gtk_application_set_menubar :: 
    Ptr Application ->                      -- application : TInterface (Name {namespace = "Gtk", name = "Application"})
    Ptr Gio.MenuModel.MenuModel ->          -- menubar : TInterface (Name {namespace = "Gio", name = "MenuModel"})
    IO ()

-- | Sets or unsets the menubar for windows of the application.
-- 
-- This is a menubar in the traditional sense.
-- 
-- This can only be done in the primary instance of the application,
-- after it has been registered. @/GIO.Application.startup()/@ is
-- a good place to call this.
-- 
-- Depending on the desktop environment, this may appear at the top of
-- each window, or at the top of the screen. In some environments, if
-- both the application menu and the menubar are set, the application
-- menu will be presented as if it were the first item of the menubar.
-- Other environments treat the two as completely separate — for example,
-- the application menu may be rendered by the desktop shell while the
-- menubar (if set) remains in each individual window.
-- 
-- Use the base @GActionMap@ interface to add actions, to respond to the
-- user selecting these menu items.
applicationSetMenubar ::
    (B.CallStack.HasCallStack, MonadIO m, IsApplication a, Gio.MenuModel.IsMenuModel b) =>
    a
    -- ^ /@application@/: an application
    -> Maybe (b)
    -- ^ /@menubar@/: a menu model
    -> m ()
applicationSetMenubar :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsApplication a, IsMenuModel b) =>
a -> Maybe b -> m ()
applicationSetMenubar a
application Maybe b
menubar = 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
    application' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
application
    maybeMenubar <- case menubar of
        Maybe b
Nothing -> Ptr MenuModel -> IO (Ptr MenuModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
forall a. Ptr a
FP.nullPtr
        Just b
jMenubar -> do
            jMenubar' <- b -> IO (Ptr MenuModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jMenubar
            return jMenubar'
    gtk_application_set_menubar application' maybeMenubar
    touchManagedPtr application
    whenJust menubar touchManagedPtr
    return ()

#if defined(ENABLE_OVERLOADING)
data ApplicationSetMenubarMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsApplication a, Gio.MenuModel.IsMenuModel b) => O.OverloadedMethod ApplicationSetMenubarMethodInfo a signature where
    overloadedMethod = applicationSetMenubar

instance O.OverloadedMethodInfo ApplicationSetMenubarMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.applicationSetMenubar",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#v:applicationSetMenubar"
        })


#endif

-- method Application::uninhibit
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "application"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Application" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the application" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cookie"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a cookie that was returned by [method@Gtk.Application.inhibit]"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_application_uninhibit" gtk_application_uninhibit :: 
    Ptr Application ->                      -- application : TInterface (Name {namespace = "Gtk", name = "Application"})
    Word32 ->                               -- cookie : TBasicType TUInt
    IO ()

-- | Removes an inhibitor that has been previously established.
-- 
-- See 'GI.Gtk.Objects.Application.applicationInhibit'.
-- 
-- Inhibitors are also cleared when the application exits.
applicationUninhibit ::
    (B.CallStack.HasCallStack, MonadIO m, IsApplication a) =>
    a
    -- ^ /@application@/: the application
    -> Word32
    -- ^ /@cookie@/: a cookie that was returned by 'GI.Gtk.Objects.Application.applicationInhibit'
    -> m ()
applicationUninhibit :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsApplication a) =>
a -> Word32 -> m ()
applicationUninhibit a
application Word32
cookie = 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
    application' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
application
    gtk_application_uninhibit application' cookie
    touchManagedPtr application
    return ()

#if defined(ENABLE_OVERLOADING)
data ApplicationUninhibitMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsApplication a) => O.OverloadedMethod ApplicationUninhibitMethodInfo a signature where
    overloadedMethod = applicationUninhibit

instance O.OverloadedMethodInfo ApplicationUninhibitMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Application.applicationUninhibit",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Application.html#v:applicationUninhibit"
        })


#endif