{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Dazzle.Objects.Application
(
Application(..) ,
IsApplication ,
toApplication ,
#if defined(ENABLE_OVERLOADING)
ResolveApplicationMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ApplicationAddResourcesMethodInfo ,
#endif
applicationAddResources ,
#if defined(ENABLE_OVERLOADING)
ApplicationGetMenuByIdMethodInfo ,
#endif
applicationGetMenuById ,
#if defined(ENABLE_OVERLOADING)
ApplicationGetMenuManagerMethodInfo ,
#endif
applicationGetMenuManager ,
#if defined(ENABLE_OVERLOADING)
ApplicationGetShortcutManagerMethodInfo ,
#endif
applicationGetShortcutManager ,
#if defined(ENABLE_OVERLOADING)
ApplicationGetThemeManagerMethodInfo ,
#endif
applicationGetThemeManager ,
applicationNew ,
#if defined(ENABLE_OVERLOADING)
ApplicationRemoveResourcesMethodInfo ,
#endif
applicationRemoveResources ,
#if defined(ENABLE_OVERLOADING)
ApplicationMenuManagerPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
applicationMenuManager ,
#endif
getApplicationMenuManager ,
#if defined(ENABLE_OVERLOADING)
ApplicationShortcutManagerPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
applicationShortcutManager ,
#endif
getApplicationShortcutManager ,
#if defined(ENABLE_OVERLOADING)
ApplicationThemeManagerPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
applicationThemeManager ,
#endif
getApplicationThemeManager ,
) 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 {-# SOURCE #-} qualified GI.Dazzle.Objects.MenuManager as Dazzle.MenuManager
import {-# SOURCE #-} qualified GI.Dazzle.Objects.ShortcutManager as Dazzle.ShortcutManager
import {-# SOURCE #-} qualified GI.Dazzle.Objects.ThemeManager as Dazzle.ThemeManager
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.Gtk.Objects.Application as Gtk.Application
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 "dzl_application_get_type"
c_dzl_application_get_type :: IO B.Types.GType
instance B.Types.TypedObject Application where
glibType :: IO GType
glibType = IO GType
c_dzl_application_get_type
instance B.Types.GObject Application
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 = '[Gtk.Application.Application, Gio.Application.Application, GObject.Object.Object, Gio.ActionGroup.ActionGroup, Gio.ActionMap.ActionMap]
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
instance B.GValue.IsGValue (Maybe Application) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_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 Application
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 Application
ptr Ptr Application -> Ptr Application -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Application
forall a. Ptr a
FP.nullPtr
then Application -> Maybe Application
forall a. a -> Maybe a
P.Just (Application -> Maybe Application)
-> IO Application -> IO (Maybe Application)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Application -> Application)
-> Ptr Application -> IO Application
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Application -> Application
Application Ptr Application
ptr
else Maybe Application -> IO (Maybe Application)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Application
forall a. Maybe a
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 "addAccelerator" o = Gtk.Application.ApplicationAddAcceleratorMethodInfo
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 "addResources" o = ApplicationAddResourcesMethodInfo
ResolveApplicationMethod "addWindow" o = Gtk.Application.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 = Gtk.Application.ApplicationInhibitMethodInfo
ResolveApplicationMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveApplicationMethod "isInhibited" o = Gtk.Application.ApplicationIsInhibitedMethodInfo
ResolveApplicationMethod "listActionDescriptions" o = Gtk.Application.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 "prefersAppMenu" o = Gtk.Application.ApplicationPrefersAppMenuMethodInfo
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 "removeAccelerator" o = Gtk.Application.ApplicationRemoveAcceleratorMethodInfo
ResolveApplicationMethod "removeAction" o = Gio.ActionMap.ActionMapRemoveActionMethodInfo
ResolveApplicationMethod "removeActionEntries" o = Gio.ActionMap.ActionMapRemoveActionEntriesMethodInfo
ResolveApplicationMethod "removeResources" o = ApplicationRemoveResourcesMethodInfo
ResolveApplicationMethod "removeWindow" o = Gtk.Application.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 = Gtk.Application.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 = Gtk.Application.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 = Gtk.Application.ApplicationGetActionsForAccelMethodInfo
ResolveApplicationMethod "getActiveWindow" o = Gtk.Application.ApplicationGetActiveWindowMethodInfo
ResolveApplicationMethod "getAppMenu" o = Gtk.Application.ApplicationGetAppMenuMethodInfo
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 "getMenuManager" o = ApplicationGetMenuManagerMethodInfo
ResolveApplicationMethod "getMenubar" o = Gtk.Application.ApplicationGetMenubarMethodInfo
ResolveApplicationMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveApplicationMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveApplicationMethod "getResourceBasePath" o = Gio.Application.ApplicationGetResourceBasePathMethodInfo
ResolveApplicationMethod "getShortcutManager" o = ApplicationGetShortcutManagerMethodInfo
ResolveApplicationMethod "getThemeManager" o = ApplicationGetThemeManagerMethodInfo
ResolveApplicationMethod "getVersion" o = Gio.Application.ApplicationGetVersionMethodInfo
ResolveApplicationMethod "getWindowById" o = Gtk.Application.ApplicationGetWindowByIdMethodInfo
ResolveApplicationMethod "getWindows" o = Gtk.Application.ApplicationGetWindowsMethodInfo
ResolveApplicationMethod "setAccelsForAction" o = Gtk.Application.ApplicationSetAccelsForActionMethodInfo
ResolveApplicationMethod "setActionGroup" o = Gio.Application.ApplicationSetActionGroupMethodInfo
ResolveApplicationMethod "setAppMenu" o = Gtk.Application.ApplicationSetAppMenuMethodInfo
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 = Gtk.Application.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
getApplicationMenuManager :: (MonadIO m, IsApplication o) => o -> m Dazzle.MenuManager.MenuManager
o
obj = IO MenuManager -> m MenuManager
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO MenuManager -> m MenuManager)
-> IO MenuManager -> m MenuManager
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe MenuManager) -> IO MenuManager
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getApplicationMenuManager" (IO (Maybe MenuManager) -> IO MenuManager)
-> IO (Maybe MenuManager) -> IO MenuManager
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr MenuManager -> MenuManager)
-> IO (Maybe MenuManager)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"menu-manager" ManagedPtr MenuManager -> MenuManager
Dazzle.MenuManager.MenuManager
#if defined(ENABLE_OVERLOADING)
data ApplicationMenuManagerPropertyInfo
instance AttrInfo ApplicationMenuManagerPropertyInfo where
type AttrAllowedOps ApplicationMenuManagerPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint ApplicationMenuManagerPropertyInfo = IsApplication
type AttrSetTypeConstraint ApplicationMenuManagerPropertyInfo = (~) ()
type AttrTransferTypeConstraint ApplicationMenuManagerPropertyInfo = (~) ()
type AttrTransferType ApplicationMenuManagerPropertyInfo = ()
type AttrGetType ApplicationMenuManagerPropertyInfo = Dazzle.MenuManager.MenuManager
type AttrLabel ApplicationMenuManagerPropertyInfo = "menu-manager"
type AttrOrigin ApplicationMenuManagerPropertyInfo = Application
attrGet = getApplicationMenuManager
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Application.menuManager"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Application.html#g:attr:menuManager"
})
#endif
getApplicationShortcutManager :: (MonadIO m, IsApplication o) => o -> m Dazzle.ShortcutManager.ShortcutManager
getApplicationShortcutManager :: forall (m :: * -> *) o.
(MonadIO m, IsApplication o) =>
o -> m ShortcutManager
getApplicationShortcutManager o
obj = IO ShortcutManager -> m ShortcutManager
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ShortcutManager -> m ShortcutManager)
-> IO ShortcutManager -> m ShortcutManager
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe ShortcutManager) -> IO ShortcutManager
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getApplicationShortcutManager" (IO (Maybe ShortcutManager) -> IO ShortcutManager)
-> IO (Maybe ShortcutManager) -> IO ShortcutManager
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr ShortcutManager -> ShortcutManager)
-> IO (Maybe ShortcutManager)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"shortcut-manager" ManagedPtr ShortcutManager -> ShortcutManager
Dazzle.ShortcutManager.ShortcutManager
#if defined(ENABLE_OVERLOADING)
data ApplicationShortcutManagerPropertyInfo
instance AttrInfo ApplicationShortcutManagerPropertyInfo where
type AttrAllowedOps ApplicationShortcutManagerPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint ApplicationShortcutManagerPropertyInfo = IsApplication
type AttrSetTypeConstraint ApplicationShortcutManagerPropertyInfo = (~) ()
type AttrTransferTypeConstraint ApplicationShortcutManagerPropertyInfo = (~) ()
type AttrTransferType ApplicationShortcutManagerPropertyInfo = ()
type AttrGetType ApplicationShortcutManagerPropertyInfo = Dazzle.ShortcutManager.ShortcutManager
type AttrLabel ApplicationShortcutManagerPropertyInfo = "shortcut-manager"
type AttrOrigin ApplicationShortcutManagerPropertyInfo = Application
attrGet = getApplicationShortcutManager
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Application.shortcutManager"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Application.html#g:attr:shortcutManager"
})
#endif
getApplicationThemeManager :: (MonadIO m, IsApplication o) => o -> m Dazzle.ThemeManager.ThemeManager
getApplicationThemeManager :: forall (m :: * -> *) o.
(MonadIO m, IsApplication o) =>
o -> m ThemeManager
getApplicationThemeManager o
obj = IO ThemeManager -> m ThemeManager
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ThemeManager -> m ThemeManager)
-> IO ThemeManager -> m ThemeManager
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe ThemeManager) -> IO ThemeManager
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getApplicationThemeManager" (IO (Maybe ThemeManager) -> IO ThemeManager)
-> IO (Maybe ThemeManager) -> IO ThemeManager
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr ThemeManager -> ThemeManager)
-> IO (Maybe ThemeManager)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"theme-manager" ManagedPtr ThemeManager -> ThemeManager
Dazzle.ThemeManager.ThemeManager
#if defined(ENABLE_OVERLOADING)
data ApplicationThemeManagerPropertyInfo
instance AttrInfo ApplicationThemeManagerPropertyInfo where
type AttrAllowedOps ApplicationThemeManagerPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint ApplicationThemeManagerPropertyInfo = IsApplication
type AttrSetTypeConstraint ApplicationThemeManagerPropertyInfo = (~) ()
type AttrTransferTypeConstraint ApplicationThemeManagerPropertyInfo = (~) ()
type AttrTransferType ApplicationThemeManagerPropertyInfo = ()
type AttrGetType ApplicationThemeManagerPropertyInfo = Dazzle.ThemeManager.ThemeManager
type AttrLabel ApplicationThemeManagerPropertyInfo = "theme-manager"
type AttrOrigin ApplicationThemeManagerPropertyInfo = Application
attrGet = getApplicationThemeManager
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Application.themeManager"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Application.html#g:attr:themeManager"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Application
type instance O.AttributeList Application = ApplicationAttributeList
type ApplicationAttributeList = ('[ '("actionGroup", Gio.Application.ApplicationActionGroupPropertyInfo), '("activeWindow", Gtk.Application.ApplicationActiveWindowPropertyInfo), '("appMenu", Gtk.Application.ApplicationAppMenuPropertyInfo), '("applicationId", Gio.Application.ApplicationApplicationIdPropertyInfo), '("flags", Gio.Application.ApplicationFlagsPropertyInfo), '("inactivityTimeout", Gio.Application.ApplicationInactivityTimeoutPropertyInfo), '("isBusy", Gio.Application.ApplicationIsBusyPropertyInfo), '("isRegistered", Gio.Application.ApplicationIsRegisteredPropertyInfo), '("isRemote", Gio.Application.ApplicationIsRemotePropertyInfo), '("menuManager", ApplicationMenuManagerPropertyInfo), '("menubar", Gtk.Application.ApplicationMenubarPropertyInfo), '("registerSession", Gtk.Application.ApplicationRegisterSessionPropertyInfo), '("resourceBasePath", Gio.Application.ApplicationResourceBasePathPropertyInfo), '("screensaverActive", Gtk.Application.ApplicationScreensaverActivePropertyInfo), '("shortcutManager", ApplicationShortcutManagerPropertyInfo), '("themeManager", ApplicationThemeManagerPropertyInfo), '("version", Gio.Application.ApplicationVersionPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
applicationMenuManager :: AttrLabelProxy "menuManager"
applicationMenuManager = AttrLabelProxy
applicationShortcutManager :: AttrLabelProxy "shortcutManager"
applicationShortcutManager = AttrLabelProxy
applicationThemeManager :: AttrLabelProxy "themeManager"
applicationThemeManager = 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", Gtk.Application.ApplicationQueryEndSignalInfo), '("shutdown", Gio.Application.ApplicationShutdownSignalInfo), '("startup", Gio.Application.ApplicationStartupSignalInfo), '("windowAdded", Gtk.Application.ApplicationWindowAddedSignalInfo), '("windowRemoved", Gtk.Application.ApplicationWindowRemovedSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "dzl_application_new" dzl_application_new ::
CString ->
CUInt ->
IO (Ptr Application)
applicationNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> [Gio.Flags.ApplicationFlags]
-> m Application
applicationNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> [ApplicationFlags] -> m Application
applicationNew 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
CString
applicationId' <- Text -> IO CString
textToCString Text
applicationId
let flags' :: CUInt
flags' = [ApplicationFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ApplicationFlags]
flags
Ptr Application
result <- CString -> CUInt -> IO (Ptr Application)
dzl_application_new CString
applicationId' CUInt
flags'
Text -> Ptr Application -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"applicationNew" Ptr Application
result
Application
result' <- ((ManagedPtr Application -> Application)
-> Ptr Application -> IO Application
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Application -> Application
Application) Ptr Application
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
applicationId'
Application -> IO Application
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Application
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "dzl_application_add_resources" dzl_application_add_resources ::
Ptr Application ->
CString ->
IO ()
applicationAddResources ::
(B.CallStack.HasCallStack, MonadIO m, IsApplication a) =>
a
-> T.Text
-> m ()
applicationAddResources :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsApplication a) =>
a -> Text -> m ()
applicationAddResources a
self Text
resourcePath = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Application
self' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
resourcePath' <- Text -> IO CString
textToCString Text
resourcePath
Ptr Application -> CString -> IO ()
dzl_application_add_resources Ptr Application
self' CString
resourcePath'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
resourcePath'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ApplicationAddResourcesMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsApplication a) => O.OverloadedMethod ApplicationAddResourcesMethodInfo a signature where
overloadedMethod = applicationAddResources
instance O.OverloadedMethodInfo ApplicationAddResourcesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Application.applicationAddResources",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Application.html#v:applicationAddResources"
})
#endif
foreign import ccall "dzl_application_get_menu_by_id" ::
Ptr Application ->
CString ->
IO (Ptr Gio.Menu.Menu)
applicationGetMenuById ::
(B.CallStack.HasCallStack, MonadIO m, IsApplication a) =>
a
-> T.Text
-> m Gio.Menu.Menu
a
self Text
menuId = IO Menu -> m Menu
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Menu -> m Menu) -> IO Menu -> m Menu
forall a b. (a -> b) -> a -> b
$ do
Ptr Application
self' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
menuId' <- Text -> IO CString
textToCString Text
menuId
Ptr Menu
result <- Ptr Application -> CString -> IO (Ptr Menu)
dzl_application_get_menu_by_id Ptr Application
self' CString
menuId'
Text -> Ptr Menu -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"applicationGetMenuById" Ptr Menu
result
Menu
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
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
menuId'
Menu -> IO Menu
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Menu
result'
#if defined(ENABLE_OVERLOADING)
data ApplicationGetMenuByIdMethodInfo
instance (signature ~ (T.Text -> m 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.Dazzle.Objects.Application.applicationGetMenuById",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Application.html#v:applicationGetMenuById"
})
#endif
foreign import ccall "dzl_application_get_menu_manager" ::
Ptr Application ->
IO (Ptr Dazzle.MenuManager.MenuManager)
applicationGetMenuManager ::
(B.CallStack.HasCallStack, MonadIO m, IsApplication a) =>
a
-> m Dazzle.MenuManager.MenuManager
a
self = IO MenuManager -> m MenuManager
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MenuManager -> m MenuManager)
-> IO MenuManager -> m MenuManager
forall a b. (a -> b) -> a -> b
$ do
Ptr Application
self' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr MenuManager
result <- Ptr Application -> IO (Ptr MenuManager)
dzl_application_get_menu_manager Ptr Application
self'
Text -> Ptr MenuManager -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"applicationGetMenuManager" Ptr MenuManager
result
MenuManager
result' <- ((ManagedPtr MenuManager -> MenuManager)
-> Ptr MenuManager -> IO MenuManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr MenuManager -> MenuManager
Dazzle.MenuManager.MenuManager) Ptr MenuManager
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
MenuManager -> IO MenuManager
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return MenuManager
result'
#if defined(ENABLE_OVERLOADING)
data ApplicationGetMenuManagerMethodInfo
instance (signature ~ (m Dazzle.MenuManager.MenuManager), MonadIO m, IsApplication a) => O.OverloadedMethod ApplicationGetMenuManagerMethodInfo a signature where
overloadedMethod = applicationGetMenuManager
instance O.OverloadedMethodInfo ApplicationGetMenuManagerMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Application.applicationGetMenuManager",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Application.html#v:applicationGetMenuManager"
})
#endif
foreign import ccall "dzl_application_get_shortcut_manager" dzl_application_get_shortcut_manager ::
Ptr Application ->
IO (Ptr Dazzle.ShortcutManager.ShortcutManager)
applicationGetShortcutManager ::
(B.CallStack.HasCallStack, MonadIO m, IsApplication a) =>
a
-> m Dazzle.ShortcutManager.ShortcutManager
applicationGetShortcutManager :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsApplication a) =>
a -> m ShortcutManager
applicationGetShortcutManager a
self = IO ShortcutManager -> m ShortcutManager
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ShortcutManager -> m ShortcutManager)
-> IO ShortcutManager -> m ShortcutManager
forall a b. (a -> b) -> a -> b
$ do
Ptr Application
self' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr ShortcutManager
result <- Ptr Application -> IO (Ptr ShortcutManager)
dzl_application_get_shortcut_manager Ptr Application
self'
Text -> Ptr ShortcutManager -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"applicationGetShortcutManager" Ptr ShortcutManager
result
ShortcutManager
result' <- ((ManagedPtr ShortcutManager -> ShortcutManager)
-> Ptr ShortcutManager -> IO ShortcutManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ShortcutManager -> ShortcutManager
Dazzle.ShortcutManager.ShortcutManager) Ptr ShortcutManager
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
ShortcutManager -> IO ShortcutManager
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ShortcutManager
result'
#if defined(ENABLE_OVERLOADING)
data ApplicationGetShortcutManagerMethodInfo
instance (signature ~ (m Dazzle.ShortcutManager.ShortcutManager), MonadIO m, IsApplication a) => O.OverloadedMethod ApplicationGetShortcutManagerMethodInfo a signature where
overloadedMethod = applicationGetShortcutManager
instance O.OverloadedMethodInfo ApplicationGetShortcutManagerMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Application.applicationGetShortcutManager",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Application.html#v:applicationGetShortcutManager"
})
#endif
foreign import ccall "dzl_application_get_theme_manager" dzl_application_get_theme_manager ::
Ptr Application ->
IO (Ptr Dazzle.ThemeManager.ThemeManager)
applicationGetThemeManager ::
(B.CallStack.HasCallStack, MonadIO m, IsApplication a) =>
a
-> m Dazzle.ThemeManager.ThemeManager
applicationGetThemeManager :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsApplication a) =>
a -> m ThemeManager
applicationGetThemeManager a
self = IO ThemeManager -> m ThemeManager
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ThemeManager -> m ThemeManager)
-> IO ThemeManager -> m ThemeManager
forall a b. (a -> b) -> a -> b
$ do
Ptr Application
self' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr ThemeManager
result <- Ptr Application -> IO (Ptr ThemeManager)
dzl_application_get_theme_manager Ptr Application
self'
Text -> Ptr ThemeManager -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"applicationGetThemeManager" Ptr ThemeManager
result
ThemeManager
result' <- ((ManagedPtr ThemeManager -> ThemeManager)
-> Ptr ThemeManager -> IO ThemeManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ThemeManager -> ThemeManager
Dazzle.ThemeManager.ThemeManager) Ptr ThemeManager
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
ThemeManager -> IO ThemeManager
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ThemeManager
result'
#if defined(ENABLE_OVERLOADING)
data ApplicationGetThemeManagerMethodInfo
instance (signature ~ (m Dazzle.ThemeManager.ThemeManager), MonadIO m, IsApplication a) => O.OverloadedMethod ApplicationGetThemeManagerMethodInfo a signature where
overloadedMethod = applicationGetThemeManager
instance O.OverloadedMethodInfo ApplicationGetThemeManagerMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Application.applicationGetThemeManager",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Application.html#v:applicationGetThemeManager"
})
#endif
foreign import ccall "dzl_application_remove_resources" dzl_application_remove_resources ::
Ptr Application ->
CString ->
IO ()
applicationRemoveResources ::
(B.CallStack.HasCallStack, MonadIO m, IsApplication a) =>
a
-> T.Text
-> m ()
applicationRemoveResources :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsApplication a) =>
a -> Text -> m ()
applicationRemoveResources a
self Text
resourcePath = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Application
self' <- a -> IO (Ptr Application)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
resourcePath' <- Text -> IO CString
textToCString Text
resourcePath
Ptr Application -> CString -> IO ()
dzl_application_remove_resources Ptr Application
self' CString
resourcePath'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
resourcePath'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ApplicationRemoveResourcesMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsApplication a) => O.OverloadedMethod ApplicationRemoveResourcesMethodInfo a signature where
overloadedMethod = applicationRemoveResources
instance O.OverloadedMethodInfo ApplicationRemoveResourcesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Application.applicationRemoveResources",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Application.html#v:applicationRemoveResources"
})
#endif