{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.Gtk.Objects.ListBoxRow.ListBoxRow' used to choose from a list of items.
-- 
-- The @HdyComboRow@ widget allows the user to choose from a list of valid
-- choices. The row displays the selected choice. When activated, the row
-- displays a popover which allows the user to make a new choice.
-- 
-- The [class/@comboRow@/] uses the model-view pattern; the list of valid choices
-- is specified in the form of a t'GI.Gio.Interfaces.ListModel.ListModel', and the display of the
-- choices can be adapted to the data in the model via widget creation
-- functions.
-- 
-- @HdyComboRow@ is [ListBoxRow:activatable]("GI.Gtk.Objects.ListBoxRow#g:attr:activatable") if a model is set.
-- 
-- == CSS nodes
-- 
-- @HdyComboRow@ has a main CSS node with name @row@.
-- 
-- Its popover has the node name popover with the @.combo@ style class, it
-- contains a t'GI.Gtk.Objects.ScrolledWindow.ScrolledWindow', which in turn contains a
-- t'GI.Gtk.Objects.ListBox.ListBox', both are accessible via their regular nodes.
-- 
-- A checkmark of node and style class @image.checkmark@ in the popover denotes
-- the current item.
-- 
-- /Since: 1.0/

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

module GI.Handy.Objects.ComboRow
    ( 

-- * Exported types
    ComboRow(..)                            ,
    IsComboRow                              ,
    toComboRow                              ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [activate]("GI.Handy.Objects.ActionRow#g:method:activate"), [add]("GI.Gtk.Objects.Container#g:method:add"), [addAccelerator]("GI.Gtk.Objects.Widget#g:method:addAccelerator"), [addChild]("GI.Gtk.Interfaces.Buildable#g:method:addChild"), [addDeviceEvents]("GI.Gtk.Objects.Widget#g:method:addDeviceEvents"), [addEvents]("GI.Gtk.Objects.Widget#g:method:addEvents"), [addMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:addMnemonicLabel"), [addPrefix]("GI.Handy.Objects.ActionRow#g:method:addPrefix"), [addTickCallback]("GI.Gtk.Objects.Widget#g:method:addTickCallback"), [bindModel]("GI.Handy.Objects.ComboRow#g:method:bindModel"), [bindNameModel]("GI.Handy.Objects.ComboRow#g:method:bindNameModel"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [canActivateAccel]("GI.Gtk.Objects.Widget#g:method:canActivateAccel"), [changed]("GI.Gtk.Objects.ListBoxRow#g:method:changed"), [checkResize]("GI.Gtk.Objects.Container#g:method:checkResize"), [childFocus]("GI.Gtk.Objects.Widget#g:method:childFocus"), [childGetProperty]("GI.Gtk.Objects.Container#g:method:childGetProperty"), [childNotify]("GI.Gtk.Objects.Container#g:method:childNotify"), [childNotifyByPspec]("GI.Gtk.Objects.Container#g:method:childNotifyByPspec"), [childSetProperty]("GI.Gtk.Objects.Container#g:method:childSetProperty"), [childType]("GI.Gtk.Objects.Container#g:method:childType"), [classPath]("GI.Gtk.Objects.Widget#g:method:classPath"), [computeExpand]("GI.Gtk.Objects.Widget#g:method:computeExpand"), [constructChild]("GI.Gtk.Interfaces.Buildable#g:method:constructChild"), [createPangoContext]("GI.Gtk.Objects.Widget#g:method:createPangoContext"), [createPangoLayout]("GI.Gtk.Objects.Widget#g:method:createPangoLayout"), [customFinished]("GI.Gtk.Interfaces.Buildable#g:method:customFinished"), [customTagEnd]("GI.Gtk.Interfaces.Buildable#g:method:customTagEnd"), [customTagStart]("GI.Gtk.Interfaces.Buildable#g:method:customTagStart"), [destroy]("GI.Gtk.Objects.Widget#g:method:destroy"), [destroyed]("GI.Gtk.Objects.Widget#g:method:destroyed"), [deviceIsShadowed]("GI.Gtk.Objects.Widget#g:method:deviceIsShadowed"), [dragBegin]("GI.Gtk.Objects.Widget#g:method:dragBegin"), [dragBeginWithCoordinates]("GI.Gtk.Objects.Widget#g:method:dragBeginWithCoordinates"), [dragCheckThreshold]("GI.Gtk.Objects.Widget#g:method:dragCheckThreshold"), [dragDestAddImageTargets]("GI.Gtk.Objects.Widget#g:method:dragDestAddImageTargets"), [dragDestAddTextTargets]("GI.Gtk.Objects.Widget#g:method:dragDestAddTextTargets"), [dragDestAddUriTargets]("GI.Gtk.Objects.Widget#g:method:dragDestAddUriTargets"), [dragDestFindTarget]("GI.Gtk.Objects.Widget#g:method:dragDestFindTarget"), [dragDestGetTargetList]("GI.Gtk.Objects.Widget#g:method:dragDestGetTargetList"), [dragDestGetTrackMotion]("GI.Gtk.Objects.Widget#g:method:dragDestGetTrackMotion"), [dragDestSet]("GI.Gtk.Objects.Widget#g:method:dragDestSet"), [dragDestSetProxy]("GI.Gtk.Objects.Widget#g:method:dragDestSetProxy"), [dragDestSetTargetList]("GI.Gtk.Objects.Widget#g:method:dragDestSetTargetList"), [dragDestSetTrackMotion]("GI.Gtk.Objects.Widget#g:method:dragDestSetTrackMotion"), [dragDestUnset]("GI.Gtk.Objects.Widget#g:method:dragDestUnset"), [dragGetData]("GI.Gtk.Objects.Widget#g:method:dragGetData"), [dragHighlight]("GI.Gtk.Objects.Widget#g:method:dragHighlight"), [dragSourceAddImageTargets]("GI.Gtk.Objects.Widget#g:method:dragSourceAddImageTargets"), [dragSourceAddTextTargets]("GI.Gtk.Objects.Widget#g:method:dragSourceAddTextTargets"), [dragSourceAddUriTargets]("GI.Gtk.Objects.Widget#g:method:dragSourceAddUriTargets"), [dragSourceGetTargetList]("GI.Gtk.Objects.Widget#g:method:dragSourceGetTargetList"), [dragSourceSet]("GI.Gtk.Objects.Widget#g:method:dragSourceSet"), [dragSourceSetIconGicon]("GI.Gtk.Objects.Widget#g:method:dragSourceSetIconGicon"), [dragSourceSetIconName]("GI.Gtk.Objects.Widget#g:method:dragSourceSetIconName"), [dragSourceSetIconPixbuf]("GI.Gtk.Objects.Widget#g:method:dragSourceSetIconPixbuf"), [dragSourceSetIconStock]("GI.Gtk.Objects.Widget#g:method:dragSourceSetIconStock"), [dragSourceSetTargetList]("GI.Gtk.Objects.Widget#g:method:dragSourceSetTargetList"), [dragSourceUnset]("GI.Gtk.Objects.Widget#g:method:dragSourceUnset"), [dragUnhighlight]("GI.Gtk.Objects.Widget#g:method:dragUnhighlight"), [draw]("GI.Gtk.Objects.Widget#g:method:draw"), [ensureStyle]("GI.Gtk.Objects.Widget#g:method:ensureStyle"), [errorBell]("GI.Gtk.Objects.Widget#g:method:errorBell"), [event]("GI.Gtk.Objects.Widget#g:method:event"), [forall]("GI.Gtk.Objects.Container#g:method:forall"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [foreach]("GI.Gtk.Objects.Container#g:method:foreach"), [freezeChildNotify]("GI.Gtk.Objects.Widget#g:method:freezeChildNotify"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [grabAdd]("GI.Gtk.Objects.Widget#g:method:grabAdd"), [grabDefault]("GI.Gtk.Objects.Widget#g:method:grabDefault"), [grabFocus]("GI.Gtk.Objects.Widget#g:method:grabFocus"), [grabRemove]("GI.Gtk.Objects.Widget#g:method:grabRemove"), [hasDefault]("GI.Gtk.Objects.Widget#g:method:hasDefault"), [hasFocus]("GI.Gtk.Objects.Widget#g:method:hasFocus"), [hasGrab]("GI.Gtk.Objects.Widget#g:method:hasGrab"), [hasRcStyle]("GI.Gtk.Objects.Widget#g:method:hasRcStyle"), [hasScreen]("GI.Gtk.Objects.Widget#g:method:hasScreen"), [hasVisibleFocus]("GI.Gtk.Objects.Widget#g:method:hasVisibleFocus"), [hide]("GI.Gtk.Objects.Widget#g:method:hide"), [hideOnDelete]("GI.Gtk.Objects.Widget#g:method:hideOnDelete"), [inDestruction]("GI.Gtk.Objects.Widget#g:method:inDestruction"), [initTemplate]("GI.Gtk.Objects.Widget#g:method:initTemplate"), [inputShapeCombineRegion]("GI.Gtk.Objects.Widget#g:method:inputShapeCombineRegion"), [insertActionGroup]("GI.Gtk.Objects.Widget#g:method:insertActionGroup"), [intersect]("GI.Gtk.Objects.Widget#g:method:intersect"), [isAncestor]("GI.Gtk.Objects.Widget#g:method:isAncestor"), [isComposited]("GI.Gtk.Objects.Widget#g:method:isComposited"), [isDrawable]("GI.Gtk.Objects.Widget#g:method:isDrawable"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isFocus]("GI.Gtk.Objects.Widget#g:method:isFocus"), [isSelected]("GI.Gtk.Objects.ListBoxRow#g:method:isSelected"), [isSensitive]("GI.Gtk.Objects.Widget#g:method:isSensitive"), [isToplevel]("GI.Gtk.Objects.Widget#g:method:isToplevel"), [isVisible]("GI.Gtk.Objects.Widget#g:method:isVisible"), [keynavFailed]("GI.Gtk.Objects.Widget#g:method:keynavFailed"), [listAccelClosures]("GI.Gtk.Objects.Widget#g:method:listAccelClosures"), [listActionPrefixes]("GI.Gtk.Objects.Widget#g:method:listActionPrefixes"), [listMnemonicLabels]("GI.Gtk.Objects.Widget#g:method:listMnemonicLabels"), [map]("GI.Gtk.Objects.Widget#g:method:map"), [mnemonicActivate]("GI.Gtk.Objects.Widget#g:method:mnemonicActivate"), [modifyBase]("GI.Gtk.Objects.Widget#g:method:modifyBase"), [modifyBg]("GI.Gtk.Objects.Widget#g:method:modifyBg"), [modifyCursor]("GI.Gtk.Objects.Widget#g:method:modifyCursor"), [modifyFg]("GI.Gtk.Objects.Widget#g:method:modifyFg"), [modifyFont]("GI.Gtk.Objects.Widget#g:method:modifyFont"), [modifyStyle]("GI.Gtk.Objects.Widget#g:method:modifyStyle"), [modifyText]("GI.Gtk.Objects.Widget#g:method:modifyText"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [overrideBackgroundColor]("GI.Gtk.Objects.Widget#g:method:overrideBackgroundColor"), [overrideColor]("GI.Gtk.Objects.Widget#g:method:overrideColor"), [overrideCursor]("GI.Gtk.Objects.Widget#g:method:overrideCursor"), [overrideFont]("GI.Gtk.Objects.Widget#g:method:overrideFont"), [overrideSymbolicColor]("GI.Gtk.Objects.Widget#g:method:overrideSymbolicColor"), [parserFinished]("GI.Gtk.Interfaces.Buildable#g:method:parserFinished"), [path]("GI.Gtk.Objects.Widget#g:method:path"), [propagateDraw]("GI.Gtk.Objects.Container#g:method:propagateDraw"), [queueAllocate]("GI.Gtk.Objects.Widget#g:method:queueAllocate"), [queueComputeExpand]("GI.Gtk.Objects.Widget#g:method:queueComputeExpand"), [queueDraw]("GI.Gtk.Objects.Widget#g:method:queueDraw"), [queueDrawArea]("GI.Gtk.Objects.Widget#g:method:queueDrawArea"), [queueDrawRegion]("GI.Gtk.Objects.Widget#g:method:queueDrawRegion"), [queueResize]("GI.Gtk.Objects.Widget#g:method:queueResize"), [queueResizeNoRedraw]("GI.Gtk.Objects.Widget#g:method:queueResizeNoRedraw"), [realize]("GI.Gtk.Objects.Widget#g:method:realize"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [regionIntersect]("GI.Gtk.Objects.Widget#g:method:regionIntersect"), [registerWindow]("GI.Gtk.Objects.Widget#g:method:registerWindow"), [remove]("GI.Gtk.Objects.Container#g:method:remove"), [removeAccelerator]("GI.Gtk.Objects.Widget#g:method:removeAccelerator"), [removeMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:removeMnemonicLabel"), [removeTickCallback]("GI.Gtk.Objects.Widget#g:method:removeTickCallback"), [renderIcon]("GI.Gtk.Objects.Widget#g:method:renderIcon"), [renderIconPixbuf]("GI.Gtk.Objects.Widget#g:method:renderIconPixbuf"), [reparent]("GI.Gtk.Objects.Widget#g:method:reparent"), [resetRcStyles]("GI.Gtk.Objects.Widget#g:method:resetRcStyles"), [resetStyle]("GI.Gtk.Objects.Widget#g:method:resetStyle"), [resizeChildren]("GI.Gtk.Objects.Container#g:method:resizeChildren"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [sendExpose]("GI.Gtk.Objects.Widget#g:method:sendExpose"), [sendFocusChange]("GI.Gtk.Objects.Widget#g:method:sendFocusChange"), [shapeCombineRegion]("GI.Gtk.Objects.Widget#g:method:shapeCombineRegion"), [show]("GI.Gtk.Objects.Widget#g:method:show"), [showAll]("GI.Gtk.Objects.Widget#g:method:showAll"), [showNow]("GI.Gtk.Objects.Widget#g:method:showNow"), [sizeAllocate]("GI.Gtk.Objects.Widget#g:method:sizeAllocate"), [sizeAllocateWithBaseline]("GI.Gtk.Objects.Widget#g:method:sizeAllocateWithBaseline"), [sizeRequest]("GI.Gtk.Objects.Widget#g:method:sizeRequest"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [styleAttach]("GI.Gtk.Objects.Widget#g:method:styleAttach"), [styleGetProperty]("GI.Gtk.Objects.Widget#g:method:styleGetProperty"), [thawChildNotify]("GI.Gtk.Objects.Widget#g:method:thawChildNotify"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [translateCoordinates]("GI.Gtk.Objects.Widget#g:method:translateCoordinates"), [triggerTooltipQuery]("GI.Gtk.Objects.Widget#g:method:triggerTooltipQuery"), [unmap]("GI.Gtk.Objects.Widget#g:method:unmap"), [unparent]("GI.Gtk.Objects.Widget#g:method:unparent"), [unrealize]("GI.Gtk.Objects.Widget#g:method:unrealize"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unregisterWindow]("GI.Gtk.Objects.Widget#g:method:unregisterWindow"), [unsetFocusChain]("GI.Gtk.Objects.Container#g:method:unsetFocusChain"), [unsetStateFlags]("GI.Gtk.Objects.Widget#g:method:unsetStateFlags"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessible]("GI.Gtk.Objects.Widget#g:method:getAccessible"), [getActionGroup]("GI.Gtk.Objects.Widget#g:method:getActionGroup"), [getActionName]("GI.Gtk.Interfaces.Actionable#g:method:getActionName"), [getActionTargetValue]("GI.Gtk.Interfaces.Actionable#g:method:getActionTargetValue"), [getActivatable]("GI.Gtk.Objects.ListBoxRow#g:method:getActivatable"), [getActivatableWidget]("GI.Handy.Objects.ActionRow#g:method:getActivatableWidget"), [getAllocatedBaseline]("GI.Gtk.Objects.Widget#g:method:getAllocatedBaseline"), [getAllocatedHeight]("GI.Gtk.Objects.Widget#g:method:getAllocatedHeight"), [getAllocatedSize]("GI.Gtk.Objects.Widget#g:method:getAllocatedSize"), [getAllocatedWidth]("GI.Gtk.Objects.Widget#g:method:getAllocatedWidth"), [getAllocation]("GI.Gtk.Objects.Widget#g:method:getAllocation"), [getAncestor]("GI.Gtk.Objects.Widget#g:method:getAncestor"), [getAppPaintable]("GI.Gtk.Objects.Widget#g:method:getAppPaintable"), [getBorderWidth]("GI.Gtk.Objects.Container#g:method:getBorderWidth"), [getCanDefault]("GI.Gtk.Objects.Widget#g:method:getCanDefault"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getChild]("GI.Gtk.Objects.Bin#g:method:getChild"), [getChildRequisition]("GI.Gtk.Objects.Widget#g:method:getChildRequisition"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getChildren]("GI.Gtk.Objects.Container#g:method:getChildren"), [getClip]("GI.Gtk.Objects.Widget#g:method:getClip"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getCompositeName]("GI.Gtk.Objects.Widget#g:method:getCompositeName"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDeviceEnabled]("GI.Gtk.Objects.Widget#g:method:getDeviceEnabled"), [getDeviceEvents]("GI.Gtk.Objects.Widget#g:method:getDeviceEvents"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getDoubleBuffered]("GI.Gtk.Objects.Widget#g:method:getDoubleBuffered"), [getEvents]("GI.Gtk.Objects.Widget#g:method:getEvents"), [getFocusChain]("GI.Gtk.Objects.Container#g:method:getFocusChain"), [getFocusChild]("GI.Gtk.Objects.Container#g:method:getFocusChild"), [getFocusHadjustment]("GI.Gtk.Objects.Container#g:method:getFocusHadjustment"), [getFocusOnClick]("GI.Gtk.Objects.Widget#g:method:getFocusOnClick"), [getFocusVadjustment]("GI.Gtk.Objects.Container#g:method:getFocusVadjustment"), [getFontMap]("GI.Gtk.Objects.Widget#g:method:getFontMap"), [getFontOptions]("GI.Gtk.Objects.Widget#g:method:getFontOptions"), [getFrameClock]("GI.Gtk.Objects.Widget#g:method:getFrameClock"), [getHalign]("GI.Gtk.Objects.Widget#g:method:getHalign"), [getHasTooltip]("GI.Gtk.Objects.Widget#g:method:getHasTooltip"), [getHasWindow]("GI.Gtk.Objects.Widget#g:method:getHasWindow"), [getHeader]("GI.Gtk.Objects.ListBoxRow#g:method:getHeader"), [getHexpand]("GI.Gtk.Objects.Widget#g:method:getHexpand"), [getHexpandSet]("GI.Gtk.Objects.Widget#g:method:getHexpandSet"), [getIconName]("GI.Handy.Objects.ActionRow#g:method:getIconName"), [getIndex]("GI.Gtk.Objects.ListBoxRow#g:method:getIndex"), [getInternalChild]("GI.Gtk.Interfaces.Buildable#g:method:getInternalChild"), [getMapped]("GI.Gtk.Objects.Widget#g:method:getMapped"), [getMarginBottom]("GI.Gtk.Objects.Widget#g:method:getMarginBottom"), [getMarginEnd]("GI.Gtk.Objects.Widget#g:method:getMarginEnd"), [getMarginLeft]("GI.Gtk.Objects.Widget#g:method:getMarginLeft"), [getMarginRight]("GI.Gtk.Objects.Widget#g:method:getMarginRight"), [getMarginStart]("GI.Gtk.Objects.Widget#g:method:getMarginStart"), [getMarginTop]("GI.Gtk.Objects.Widget#g:method:getMarginTop"), [getModel]("GI.Handy.Objects.ComboRow#g:method:getModel"), [getModifierMask]("GI.Gtk.Objects.Widget#g:method:getModifierMask"), [getModifierStyle]("GI.Gtk.Objects.Widget#g:method:getModifierStyle"), [getName]("GI.Gtk.Objects.Widget#g:method:getName"), [getNoShowAll]("GI.Gtk.Objects.Widget#g:method:getNoShowAll"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getParentWindow]("GI.Gtk.Objects.Widget#g:method:getParentWindow"), [getPath]("GI.Gtk.Objects.Widget#g:method:getPath"), [getPathForChild]("GI.Gtk.Objects.Container#g:method:getPathForChild"), [getPointer]("GI.Gtk.Objects.Widget#g:method:getPointer"), [getPreferredHeight]("GI.Gtk.Objects.Widget#g:method:getPreferredHeight"), [getPreferredHeightAndBaselineForWidth]("GI.Gtk.Objects.Widget#g:method:getPreferredHeightAndBaselineForWidth"), [getPreferredHeightForWidth]("GI.Gtk.Objects.Widget#g:method:getPreferredHeightForWidth"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPreferredWidth]("GI.Gtk.Objects.Widget#g:method:getPreferredWidth"), [getPreferredWidthForHeight]("GI.Gtk.Objects.Widget#g:method:getPreferredWidthForHeight"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRealized]("GI.Gtk.Objects.Widget#g:method:getRealized"), [getReceivesDefault]("GI.Gtk.Objects.Widget#g:method:getReceivesDefault"), [getRequestMode]("GI.Gtk.Objects.Widget#g:method:getRequestMode"), [getRequisition]("GI.Gtk.Objects.Widget#g:method:getRequisition"), [getResizeMode]("GI.Gtk.Objects.Container#g:method:getResizeMode"), [getRootWindow]("GI.Gtk.Objects.Widget#g:method:getRootWindow"), [getScaleFactor]("GI.Gtk.Objects.Widget#g:method:getScaleFactor"), [getScreen]("GI.Gtk.Objects.Widget#g:method:getScreen"), [getSelectable]("GI.Gtk.Objects.ListBoxRow#g:method:getSelectable"), [getSelectedIndex]("GI.Handy.Objects.ComboRow#g:method:getSelectedIndex"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getSizeRequest]("GI.Gtk.Objects.Widget#g:method:getSizeRequest"), [getState]("GI.Gtk.Objects.Widget#g:method:getState"), [getStateFlags]("GI.Gtk.Objects.Widget#g:method:getStateFlags"), [getStyle]("GI.Gtk.Objects.Widget#g:method:getStyle"), [getStyleContext]("GI.Gtk.Objects.Widget#g:method:getStyleContext"), [getSubtitle]("GI.Handy.Objects.ActionRow#g:method:getSubtitle"), [getSubtitleLines]("GI.Handy.Objects.ActionRow#g:method:getSubtitleLines"), [getSupportMultidevice]("GI.Gtk.Objects.Widget#g:method:getSupportMultidevice"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [getTitle]("GI.Handy.Objects.PreferencesRow#g:method:getTitle"), [getTitleLines]("GI.Handy.Objects.ActionRow#g:method:getTitleLines"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [getTooltipWindow]("GI.Gtk.Objects.Widget#g:method:getTooltipWindow"), [getToplevel]("GI.Gtk.Objects.Widget#g:method:getToplevel"), [getUseSubtitle]("GI.Handy.Objects.ComboRow#g:method:getUseSubtitle"), [getUseUnderline]("GI.Handy.Objects.ActionRow#g:method:getUseUnderline"), [getValign]("GI.Gtk.Objects.Widget#g:method:getValign"), [getValignWithBaseline]("GI.Gtk.Objects.Widget#g:method:getValignWithBaseline"), [getVexpand]("GI.Gtk.Objects.Widget#g:method:getVexpand"), [getVexpandSet]("GI.Gtk.Objects.Widget#g:method:getVexpandSet"), [getVisible]("GI.Gtk.Objects.Widget#g:method:getVisible"), [getVisual]("GI.Gtk.Objects.Widget#g:method:getVisual"), [getWindow]("GI.Gtk.Objects.Widget#g:method:getWindow").
-- 
-- ==== Setters
-- [setAccelPath]("GI.Gtk.Objects.Widget#g:method:setAccelPath"), [setActionName]("GI.Gtk.Interfaces.Actionable#g:method:setActionName"), [setActionTargetValue]("GI.Gtk.Interfaces.Actionable#g:method:setActionTargetValue"), [setActivatable]("GI.Gtk.Objects.ListBoxRow#g:method:setActivatable"), [setActivatableWidget]("GI.Handy.Objects.ActionRow#g:method:setActivatableWidget"), [setAllocation]("GI.Gtk.Objects.Widget#g:method:setAllocation"), [setAppPaintable]("GI.Gtk.Objects.Widget#g:method:setAppPaintable"), [setBorderWidth]("GI.Gtk.Objects.Container#g:method:setBorderWidth"), [setBuildableProperty]("GI.Gtk.Interfaces.Buildable#g:method:setBuildableProperty"), [setCanDefault]("GI.Gtk.Objects.Widget#g:method:setCanDefault"), [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setClip]("GI.Gtk.Objects.Widget#g:method:setClip"), [setCompositeName]("GI.Gtk.Objects.Widget#g:method:setCompositeName"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDetailedActionName]("GI.Gtk.Interfaces.Actionable#g:method:setDetailedActionName"), [setDeviceEnabled]("GI.Gtk.Objects.Widget#g:method:setDeviceEnabled"), [setDeviceEvents]("GI.Gtk.Objects.Widget#g:method:setDeviceEvents"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setDoubleBuffered]("GI.Gtk.Objects.Widget#g:method:setDoubleBuffered"), [setEvents]("GI.Gtk.Objects.Widget#g:method:setEvents"), [setFocusChain]("GI.Gtk.Objects.Container#g:method:setFocusChain"), [setFocusChild]("GI.Gtk.Objects.Container#g:method:setFocusChild"), [setFocusHadjustment]("GI.Gtk.Objects.Container#g:method:setFocusHadjustment"), [setFocusOnClick]("GI.Gtk.Objects.Widget#g:method:setFocusOnClick"), [setFocusVadjustment]("GI.Gtk.Objects.Container#g:method:setFocusVadjustment"), [setFontMap]("GI.Gtk.Objects.Widget#g:method:setFontMap"), [setFontOptions]("GI.Gtk.Objects.Widget#g:method:setFontOptions"), [setForEnum]("GI.Handy.Objects.ComboRow#g:method:setForEnum"), [setGetNameFunc]("GI.Handy.Objects.ComboRow#g:method:setGetNameFunc"), [setHalign]("GI.Gtk.Objects.Widget#g:method:setHalign"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHasWindow]("GI.Gtk.Objects.Widget#g:method:setHasWindow"), [setHeader]("GI.Gtk.Objects.ListBoxRow#g:method:setHeader"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setIconName]("GI.Handy.Objects.ActionRow#g:method:setIconName"), [setMapped]("GI.Gtk.Objects.Widget#g:method:setMapped"), [setMarginBottom]("GI.Gtk.Objects.Widget#g:method:setMarginBottom"), [setMarginEnd]("GI.Gtk.Objects.Widget#g:method:setMarginEnd"), [setMarginLeft]("GI.Gtk.Objects.Widget#g:method:setMarginLeft"), [setMarginRight]("GI.Gtk.Objects.Widget#g:method:setMarginRight"), [setMarginStart]("GI.Gtk.Objects.Widget#g:method:setMarginStart"), [setMarginTop]("GI.Gtk.Objects.Widget#g:method:setMarginTop"), [setName]("GI.Gtk.Objects.Widget#g:method:setName"), [setNoShowAll]("GI.Gtk.Objects.Widget#g:method:setNoShowAll"), [setOpacity]("GI.Gtk.Objects.Widget#g:method:setOpacity"), [setParent]("GI.Gtk.Objects.Widget#g:method:setParent"), [setParentWindow]("GI.Gtk.Objects.Widget#g:method:setParentWindow"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setRealized]("GI.Gtk.Objects.Widget#g:method:setRealized"), [setReallocateRedraws]("GI.Gtk.Objects.Container#g:method:setReallocateRedraws"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setRedrawOnAllocate]("GI.Gtk.Objects.Widget#g:method:setRedrawOnAllocate"), [setResizeMode]("GI.Gtk.Objects.Container#g:method:setResizeMode"), [setSelectable]("GI.Gtk.Objects.ListBoxRow#g:method:setSelectable"), [setSelectedIndex]("GI.Handy.Objects.ComboRow#g:method:setSelectedIndex"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setState]("GI.Gtk.Objects.Widget#g:method:setState"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setStyle]("GI.Gtk.Objects.Widget#g:method:setStyle"), [setSubtitle]("GI.Handy.Objects.ActionRow#g:method:setSubtitle"), [setSubtitleLines]("GI.Handy.Objects.ActionRow#g:method:setSubtitleLines"), [setSupportMultidevice]("GI.Gtk.Objects.Widget#g:method:setSupportMultidevice"), [setTitle]("GI.Handy.Objects.PreferencesRow#g:method:setTitle"), [setTitleLines]("GI.Handy.Objects.ActionRow#g:method:setTitleLines"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [setTooltipWindow]("GI.Gtk.Objects.Widget#g:method:setTooltipWindow"), [setUseSubtitle]("GI.Handy.Objects.ComboRow#g:method:setUseSubtitle"), [setUseUnderline]("GI.Handy.Objects.ActionRow#g:method:setUseUnderline"), [setValign]("GI.Gtk.Objects.Widget#g:method:setValign"), [setVexpand]("GI.Gtk.Objects.Widget#g:method:setVexpand"), [setVexpandSet]("GI.Gtk.Objects.Widget#g:method:setVexpandSet"), [setVisible]("GI.Gtk.Objects.Widget#g:method:setVisible"), [setVisual]("GI.Gtk.Objects.Widget#g:method:setVisual"), [setWindow]("GI.Gtk.Objects.Widget#g:method:setWindow").

#if defined(ENABLE_OVERLOADING)
    ResolveComboRowMethod                   ,
#endif

-- ** bindModel #method:bindModel#

#if defined(ENABLE_OVERLOADING)
    ComboRowBindModelMethodInfo             ,
#endif
    comboRowBindModel                       ,


-- ** bindNameModel #method:bindNameModel#

#if defined(ENABLE_OVERLOADING)
    ComboRowBindNameModelMethodInfo         ,
#endif
    comboRowBindNameModel                   ,


-- ** getModel #method:getModel#

#if defined(ENABLE_OVERLOADING)
    ComboRowGetModelMethodInfo              ,
#endif
    comboRowGetModel                        ,


-- ** getSelectedIndex #method:getSelectedIndex#

#if defined(ENABLE_OVERLOADING)
    ComboRowGetSelectedIndexMethodInfo      ,
#endif
    comboRowGetSelectedIndex                ,


-- ** getUseSubtitle #method:getUseSubtitle#

#if defined(ENABLE_OVERLOADING)
    ComboRowGetUseSubtitleMethodInfo        ,
#endif
    comboRowGetUseSubtitle                  ,


-- ** new #method:new#

    comboRowNew                             ,


-- ** setForEnum #method:setForEnum#

#if defined(ENABLE_OVERLOADING)
    ComboRowSetForEnumMethodInfo            ,
#endif
    comboRowSetForEnum                      ,


-- ** setGetNameFunc #method:setGetNameFunc#

#if defined(ENABLE_OVERLOADING)
    ComboRowSetGetNameFuncMethodInfo        ,
#endif
    comboRowSetGetNameFunc                  ,


-- ** setSelectedIndex #method:setSelectedIndex#

#if defined(ENABLE_OVERLOADING)
    ComboRowSetSelectedIndexMethodInfo      ,
#endif
    comboRowSetSelectedIndex                ,


-- ** setUseSubtitle #method:setUseSubtitle#

#if defined(ENABLE_OVERLOADING)
    ComboRowSetUseSubtitleMethodInfo        ,
#endif
    comboRowSetUseSubtitle                  ,




 -- * Properties


-- ** selectedIndex #attr:selectedIndex#
-- | The index of the selected item in its t'GI.Gio.Interfaces.ListModel.ListModel'.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    ComboRowSelectedIndexPropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    comboRowSelectedIndex                   ,
#endif
    constructComboRowSelectedIndex          ,
    getComboRowSelectedIndex                ,
    setComboRowSelectedIndex                ,


-- ** useSubtitle #attr:useSubtitle#
-- | Whether to use the current value as the subtitle.
-- 
-- If you use a custom widget creation function, you will need to give the row
-- a name conversion closure with [method/@comboRow@/.set_get_name_func].
-- 
-- If @TRUE@, you should not access [property/@actionRow@/:subtitle].
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    ComboRowUseSubtitlePropertyInfo         ,
#endif
#if defined(ENABLE_OVERLOADING)
    comboRowUseSubtitle                     ,
#endif
    constructComboRowUseSubtitle            ,
    getComboRowUseSubtitle                  ,
    setComboRowUseSubtitle                  ,




    ) where

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

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

import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import qualified GI.Gtk.Interfaces.Actionable as Gtk.Actionable
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Objects.Bin as Gtk.Bin
import qualified GI.Gtk.Objects.Container as Gtk.Container
import qualified GI.Gtk.Objects.ListBoxRow as Gtk.ListBoxRow
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
import qualified GI.Handy.Callbacks as Handy.Callbacks
import {-# SOURCE #-} qualified GI.Handy.Objects.ActionRow as Handy.ActionRow
import {-# SOURCE #-} qualified GI.Handy.Objects.PreferencesRow as Handy.PreferencesRow

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

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

foreign import ccall "hdy_combo_row_get_type"
    c_hdy_combo_row_get_type :: IO B.Types.GType

instance B.Types.TypedObject ComboRow where
    glibType :: IO GType
glibType = IO GType
c_hdy_combo_row_get_type

instance B.Types.GObject ComboRow

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

instance O.HasParentTypes ComboRow
type instance O.ParentTypes ComboRow = '[Handy.ActionRow.ActionRow, Handy.PreferencesRow.PreferencesRow, Gtk.ListBoxRow.ListBoxRow, Gtk.Bin.Bin, Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Actionable.Actionable, Gtk.Buildable.Buildable]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveComboRowMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveComboRowMethod "activate" o = Handy.ActionRow.ActionRowActivateMethodInfo
    ResolveComboRowMethod "add" o = Gtk.Container.ContainerAddMethodInfo
    ResolveComboRowMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
    ResolveComboRowMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolveComboRowMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
    ResolveComboRowMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
    ResolveComboRowMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveComboRowMethod "addPrefix" o = Handy.ActionRow.ActionRowAddPrefixMethodInfo
    ResolveComboRowMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveComboRowMethod "bindModel" o = ComboRowBindModelMethodInfo
    ResolveComboRowMethod "bindNameModel" o = ComboRowBindNameModelMethodInfo
    ResolveComboRowMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveComboRowMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveComboRowMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
    ResolveComboRowMethod "changed" o = Gtk.ListBoxRow.ListBoxRowChangedMethodInfo
    ResolveComboRowMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
    ResolveComboRowMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveComboRowMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
    ResolveComboRowMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
    ResolveComboRowMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
    ResolveComboRowMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
    ResolveComboRowMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
    ResolveComboRowMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
    ResolveComboRowMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveComboRowMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveComboRowMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveComboRowMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveComboRowMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolveComboRowMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolveComboRowMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolveComboRowMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
    ResolveComboRowMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
    ResolveComboRowMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
    ResolveComboRowMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
    ResolveComboRowMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
    ResolveComboRowMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveComboRowMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
    ResolveComboRowMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
    ResolveComboRowMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
    ResolveComboRowMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
    ResolveComboRowMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
    ResolveComboRowMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
    ResolveComboRowMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
    ResolveComboRowMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
    ResolveComboRowMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
    ResolveComboRowMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
    ResolveComboRowMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
    ResolveComboRowMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
    ResolveComboRowMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
    ResolveComboRowMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
    ResolveComboRowMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
    ResolveComboRowMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
    ResolveComboRowMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
    ResolveComboRowMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
    ResolveComboRowMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
    ResolveComboRowMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
    ResolveComboRowMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
    ResolveComboRowMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
    ResolveComboRowMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
    ResolveComboRowMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
    ResolveComboRowMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
    ResolveComboRowMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
    ResolveComboRowMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
    ResolveComboRowMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveComboRowMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
    ResolveComboRowMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
    ResolveComboRowMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveComboRowMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
    ResolveComboRowMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
    ResolveComboRowMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveComboRowMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveComboRowMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
    ResolveComboRowMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
    ResolveComboRowMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveComboRowMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
    ResolveComboRowMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveComboRowMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveComboRowMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
    ResolveComboRowMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
    ResolveComboRowMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
    ResolveComboRowMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveComboRowMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveComboRowMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
    ResolveComboRowMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveComboRowMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveComboRowMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
    ResolveComboRowMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveComboRowMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
    ResolveComboRowMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveComboRowMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
    ResolveComboRowMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveComboRowMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveComboRowMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveComboRowMethod "isSelected" o = Gtk.ListBoxRow.ListBoxRowIsSelectedMethodInfo
    ResolveComboRowMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveComboRowMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
    ResolveComboRowMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveComboRowMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveComboRowMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
    ResolveComboRowMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
    ResolveComboRowMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveComboRowMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveComboRowMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveComboRowMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
    ResolveComboRowMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
    ResolveComboRowMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
    ResolveComboRowMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
    ResolveComboRowMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
    ResolveComboRowMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
    ResolveComboRowMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
    ResolveComboRowMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveComboRowMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveComboRowMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
    ResolveComboRowMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
    ResolveComboRowMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
    ResolveComboRowMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
    ResolveComboRowMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
    ResolveComboRowMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveComboRowMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
    ResolveComboRowMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
    ResolveComboRowMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveComboRowMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
    ResolveComboRowMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveComboRowMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
    ResolveComboRowMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
    ResolveComboRowMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveComboRowMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
    ResolveComboRowMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveComboRowMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveComboRowMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveComboRowMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
    ResolveComboRowMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
    ResolveComboRowMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
    ResolveComboRowMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
    ResolveComboRowMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveComboRowMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveComboRowMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
    ResolveComboRowMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
    ResolveComboRowMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
    ResolveComboRowMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
    ResolveComboRowMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
    ResolveComboRowMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
    ResolveComboRowMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveComboRowMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
    ResolveComboRowMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
    ResolveComboRowMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
    ResolveComboRowMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveComboRowMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
    ResolveComboRowMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
    ResolveComboRowMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveComboRowMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
    ResolveComboRowMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
    ResolveComboRowMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveComboRowMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveComboRowMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
    ResolveComboRowMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
    ResolveComboRowMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
    ResolveComboRowMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveComboRowMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveComboRowMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveComboRowMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveComboRowMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveComboRowMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveComboRowMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveComboRowMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
    ResolveComboRowMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
    ResolveComboRowMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveComboRowMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveComboRowMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
    ResolveComboRowMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
    ResolveComboRowMethod "getActionName" o = Gtk.Actionable.ActionableGetActionNameMethodInfo
    ResolveComboRowMethod "getActionTargetValue" o = Gtk.Actionable.ActionableGetActionTargetValueMethodInfo
    ResolveComboRowMethod "getActivatable" o = Gtk.ListBoxRow.ListBoxRowGetActivatableMethodInfo
    ResolveComboRowMethod "getActivatableWidget" o = Handy.ActionRow.ActionRowGetActivatableWidgetMethodInfo
    ResolveComboRowMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveComboRowMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveComboRowMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
    ResolveComboRowMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveComboRowMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveComboRowMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveComboRowMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
    ResolveComboRowMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
    ResolveComboRowMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
    ResolveComboRowMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveComboRowMethod "getChild" o = Gtk.Bin.BinGetChildMethodInfo
    ResolveComboRowMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
    ResolveComboRowMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveComboRowMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
    ResolveComboRowMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
    ResolveComboRowMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveComboRowMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
    ResolveComboRowMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveComboRowMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
    ResolveComboRowMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
    ResolveComboRowMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveComboRowMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveComboRowMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
    ResolveComboRowMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
    ResolveComboRowMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
    ResolveComboRowMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
    ResolveComboRowMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
    ResolveComboRowMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveComboRowMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
    ResolveComboRowMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveComboRowMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveComboRowMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveComboRowMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveComboRowMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveComboRowMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
    ResolveComboRowMethod "getHeader" o = Gtk.ListBoxRow.ListBoxRowGetHeaderMethodInfo
    ResolveComboRowMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveComboRowMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveComboRowMethod "getIconName" o = Handy.ActionRow.ActionRowGetIconNameMethodInfo
    ResolveComboRowMethod "getIndex" o = Gtk.ListBoxRow.ListBoxRowGetIndexMethodInfo
    ResolveComboRowMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolveComboRowMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveComboRowMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveComboRowMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveComboRowMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
    ResolveComboRowMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
    ResolveComboRowMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveComboRowMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveComboRowMethod "getModel" o = ComboRowGetModelMethodInfo
    ResolveComboRowMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
    ResolveComboRowMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
    ResolveComboRowMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveComboRowMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
    ResolveComboRowMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveComboRowMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveComboRowMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveComboRowMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
    ResolveComboRowMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
    ResolveComboRowMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
    ResolveComboRowMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
    ResolveComboRowMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
    ResolveComboRowMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
    ResolveComboRowMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
    ResolveComboRowMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveComboRowMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
    ResolveComboRowMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
    ResolveComboRowMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveComboRowMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveComboRowMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveComboRowMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveComboRowMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveComboRowMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
    ResolveComboRowMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
    ResolveComboRowMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
    ResolveComboRowMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveComboRowMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
    ResolveComboRowMethod "getSelectable" o = Gtk.ListBoxRow.ListBoxRowGetSelectableMethodInfo
    ResolveComboRowMethod "getSelectedIndex" o = ComboRowGetSelectedIndexMethodInfo
    ResolveComboRowMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveComboRowMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveComboRowMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveComboRowMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
    ResolveComboRowMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveComboRowMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
    ResolveComboRowMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveComboRowMethod "getSubtitle" o = Handy.ActionRow.ActionRowGetSubtitleMethodInfo
    ResolveComboRowMethod "getSubtitleLines" o = Handy.ActionRow.ActionRowGetSubtitleLinesMethodInfo
    ResolveComboRowMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
    ResolveComboRowMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveComboRowMethod "getTitle" o = Handy.PreferencesRow.PreferencesRowGetTitleMethodInfo
    ResolveComboRowMethod "getTitleLines" o = Handy.ActionRow.ActionRowGetTitleLinesMethodInfo
    ResolveComboRowMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveComboRowMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveComboRowMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
    ResolveComboRowMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
    ResolveComboRowMethod "getUseSubtitle" o = ComboRowGetUseSubtitleMethodInfo
    ResolveComboRowMethod "getUseUnderline" o = Handy.ActionRow.ActionRowGetUseUnderlineMethodInfo
    ResolveComboRowMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveComboRowMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
    ResolveComboRowMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveComboRowMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveComboRowMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveComboRowMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
    ResolveComboRowMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
    ResolveComboRowMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
    ResolveComboRowMethod "setActionName" o = Gtk.Actionable.ActionableSetActionNameMethodInfo
    ResolveComboRowMethod "setActionTargetValue" o = Gtk.Actionable.ActionableSetActionTargetValueMethodInfo
    ResolveComboRowMethod "setActivatable" o = Gtk.ListBoxRow.ListBoxRowSetActivatableMethodInfo
    ResolveComboRowMethod "setActivatableWidget" o = Handy.ActionRow.ActionRowSetActivatableWidgetMethodInfo
    ResolveComboRowMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
    ResolveComboRowMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
    ResolveComboRowMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
    ResolveComboRowMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveComboRowMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
    ResolveComboRowMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveComboRowMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveComboRowMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
    ResolveComboRowMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
    ResolveComboRowMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveComboRowMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveComboRowMethod "setDetailedActionName" o = Gtk.Actionable.ActionableSetDetailedActionNameMethodInfo
    ResolveComboRowMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
    ResolveComboRowMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
    ResolveComboRowMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveComboRowMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
    ResolveComboRowMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
    ResolveComboRowMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
    ResolveComboRowMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
    ResolveComboRowMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
    ResolveComboRowMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveComboRowMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
    ResolveComboRowMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveComboRowMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveComboRowMethod "setForEnum" o = ComboRowSetForEnumMethodInfo
    ResolveComboRowMethod "setGetNameFunc" o = ComboRowSetGetNameFuncMethodInfo
    ResolveComboRowMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveComboRowMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveComboRowMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
    ResolveComboRowMethod "setHeader" o = Gtk.ListBoxRow.ListBoxRowSetHeaderMethodInfo
    ResolveComboRowMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveComboRowMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveComboRowMethod "setIconName" o = Handy.ActionRow.ActionRowSetIconNameMethodInfo
    ResolveComboRowMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
    ResolveComboRowMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveComboRowMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveComboRowMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
    ResolveComboRowMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
    ResolveComboRowMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveComboRowMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveComboRowMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveComboRowMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
    ResolveComboRowMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveComboRowMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveComboRowMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
    ResolveComboRowMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveComboRowMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
    ResolveComboRowMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
    ResolveComboRowMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveComboRowMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
    ResolveComboRowMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
    ResolveComboRowMethod "setSelectable" o = Gtk.ListBoxRow.ListBoxRowSetSelectableMethodInfo
    ResolveComboRowMethod "setSelectedIndex" o = ComboRowSetSelectedIndexMethodInfo
    ResolveComboRowMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveComboRowMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveComboRowMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
    ResolveComboRowMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveComboRowMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
    ResolveComboRowMethod "setSubtitle" o = Handy.ActionRow.ActionRowSetSubtitleMethodInfo
    ResolveComboRowMethod "setSubtitleLines" o = Handy.ActionRow.ActionRowSetSubtitleLinesMethodInfo
    ResolveComboRowMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
    ResolveComboRowMethod "setTitle" o = Handy.PreferencesRow.PreferencesRowSetTitleMethodInfo
    ResolveComboRowMethod "setTitleLines" o = Handy.ActionRow.ActionRowSetTitleLinesMethodInfo
    ResolveComboRowMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveComboRowMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveComboRowMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
    ResolveComboRowMethod "setUseSubtitle" o = ComboRowSetUseSubtitleMethodInfo
    ResolveComboRowMethod "setUseUnderline" o = Handy.ActionRow.ActionRowSetUseUnderlineMethodInfo
    ResolveComboRowMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveComboRowMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveComboRowMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveComboRowMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveComboRowMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
    ResolveComboRowMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
    ResolveComboRowMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

--- XXX Duplicated object with different types:
  --- Name {namespace = "Handy", name = "ActionRow"} -> Property {propName = "use-underline", propType = TBasicType TBoolean, propFlags = [PropertyReadable,PropertyWritable], propReadNullable = Just False, propWriteNullable = Just False, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "Whether embedded underlines in the title or subtitle indicates a mnemonic.\n\nIf true, an underline in the text of the title or subtitle labels indicates\nthe next character should be used for the mnemonic accelerator key.", sinceVersion = Just "1.0"}, propDeprecated = Nothing}
  --- Name {namespace = "Handy", name = "PreferencesRow"} -> Property {propName = "use-underline", propType = TBasicType TBoolean, propFlags = [PropertyReadable,PropertyWritable], propReadNullable = Just False, propWriteNullable = Just False, propTransfer = TransferNothing, propDoc = Documentation {rawDocText = Just "Whether an embedded underline in the title indicates a mnemonic.", sinceVersion = Just "1.0"}, propDeprecated = Nothing}
-- VVV Prop "selected-index"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@selected-index@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' comboRow #selectedIndex
-- @
getComboRowSelectedIndex :: (MonadIO m, IsComboRow o) => o -> m Int32
getComboRowSelectedIndex :: forall (m :: * -> *) o. (MonadIO m, IsComboRow o) => o -> m Int32
getComboRowSelectedIndex o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"selected-index"

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

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

#if defined(ENABLE_OVERLOADING)
data ComboRowSelectedIndexPropertyInfo
instance AttrInfo ComboRowSelectedIndexPropertyInfo where
    type AttrAllowedOps ComboRowSelectedIndexPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ComboRowSelectedIndexPropertyInfo = IsComboRow
    type AttrSetTypeConstraint ComboRowSelectedIndexPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint ComboRowSelectedIndexPropertyInfo = (~) Int32
    type AttrTransferType ComboRowSelectedIndexPropertyInfo = Int32
    type AttrGetType ComboRowSelectedIndexPropertyInfo = Int32
    type AttrLabel ComboRowSelectedIndexPropertyInfo = "selected-index"
    type AttrOrigin ComboRowSelectedIndexPropertyInfo = ComboRow
    attrGet = getComboRowSelectedIndex
    attrSet = setComboRowSelectedIndex
    attrTransfer _ v = do
        return v
    attrConstruct = constructComboRowSelectedIndex
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.ComboRow.selectedIndex"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.4/docs/GI-Handy-Objects-ComboRow.html#g:attr:selectedIndex"
        })
#endif

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data ComboRowUseSubtitlePropertyInfo
instance AttrInfo ComboRowUseSubtitlePropertyInfo where
    type AttrAllowedOps ComboRowUseSubtitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ComboRowUseSubtitlePropertyInfo = IsComboRow
    type AttrSetTypeConstraint ComboRowUseSubtitlePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint ComboRowUseSubtitlePropertyInfo = (~) Bool
    type AttrTransferType ComboRowUseSubtitlePropertyInfo = Bool
    type AttrGetType ComboRowUseSubtitlePropertyInfo = Bool
    type AttrLabel ComboRowUseSubtitlePropertyInfo = "use-subtitle"
    type AttrOrigin ComboRowUseSubtitlePropertyInfo = ComboRow
    attrGet = getComboRowUseSubtitle
    attrSet = setComboRowUseSubtitle
    attrTransfer _ v = do
        return v
    attrConstruct = constructComboRowUseSubtitle
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.ComboRow.useSubtitle"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.4/docs/GI-Handy-Objects-ComboRow.html#g:attr:useSubtitle"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ComboRow
type instance O.AttributeList ComboRow = ComboRowAttributeList
type ComboRowAttributeList = ('[ '("actionName", Gtk.Actionable.ActionableActionNamePropertyInfo), '("actionTarget", Gtk.Actionable.ActionableActionTargetPropertyInfo), '("activatable", Gtk.ListBoxRow.ListBoxRowActivatablePropertyInfo), '("activatableWidget", Handy.ActionRow.ActionRowActivatableWidgetPropertyInfo), '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("borderWidth", Gtk.Container.ContainerBorderWidthPropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("child", Gtk.Container.ContainerChildPropertyInfo), '("compositeChild", Gtk.Widget.WidgetCompositeChildPropertyInfo), '("doubleBuffered", Gtk.Widget.WidgetDoubleBufferedPropertyInfo), '("events", Gtk.Widget.WidgetEventsPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("iconName", Handy.ActionRow.ActionRowIconNamePropertyInfo), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("margin", Gtk.Widget.WidgetMarginPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginLeft", Gtk.Widget.WidgetMarginLeftPropertyInfo), '("marginRight", Gtk.Widget.WidgetMarginRightPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("noShowAll", Gtk.Widget.WidgetNoShowAllPropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("resizeMode", Gtk.Container.ContainerResizeModePropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("selectable", Gtk.ListBoxRow.ListBoxRowSelectablePropertyInfo), '("selectedIndex", ComboRowSelectedIndexPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("subtitle", Handy.ActionRow.ActionRowSubtitlePropertyInfo), '("subtitleLines", Handy.ActionRow.ActionRowSubtitleLinesPropertyInfo), '("title", Handy.PreferencesRow.PreferencesRowTitlePropertyInfo), '("titleLines", Handy.ActionRow.ActionRowTitleLinesPropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("useSubtitle", ComboRowUseSubtitlePropertyInfo), '("useUnderline", Handy.ActionRow.ActionRowUseUnderlinePropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("window", Gtk.Widget.WidgetWindowPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
comboRowSelectedIndex :: AttrLabelProxy "selectedIndex"
comboRowSelectedIndex = AttrLabelProxy

comboRowUseSubtitle :: AttrLabelProxy "useSubtitle"
comboRowUseSubtitle = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ComboRow = ComboRowSignalList
type ComboRowSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("activate", Gtk.ListBoxRow.ListBoxRowActivateSignalInfo), '("activated", Handy.ActionRow.ActionRowActivatedSignalInfo), '("add", Gtk.Container.ContainerAddSignalInfo), '("buttonPressEvent", Gtk.Widget.WidgetButtonPressEventSignalInfo), '("buttonReleaseEvent", Gtk.Widget.WidgetButtonReleaseEventSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("checkResize", Gtk.Container.ContainerCheckResizeSignalInfo), '("childNotify", Gtk.Widget.WidgetChildNotifySignalInfo), '("compositedChanged", Gtk.Widget.WidgetCompositedChangedSignalInfo), '("configureEvent", Gtk.Widget.WidgetConfigureEventSignalInfo), '("damageEvent", Gtk.Widget.WidgetDamageEventSignalInfo), '("deleteEvent", Gtk.Widget.WidgetDeleteEventSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("destroyEvent", Gtk.Widget.WidgetDestroyEventSignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("dragBegin", Gtk.Widget.WidgetDragBeginSignalInfo), '("dragDataDelete", Gtk.Widget.WidgetDragDataDeleteSignalInfo), '("dragDataGet", Gtk.Widget.WidgetDragDataGetSignalInfo), '("dragDataReceived", Gtk.Widget.WidgetDragDataReceivedSignalInfo), '("dragDrop", Gtk.Widget.WidgetDragDropSignalInfo), '("dragEnd", Gtk.Widget.WidgetDragEndSignalInfo), '("dragFailed", Gtk.Widget.WidgetDragFailedSignalInfo), '("dragLeave", Gtk.Widget.WidgetDragLeaveSignalInfo), '("dragMotion", Gtk.Widget.WidgetDragMotionSignalInfo), '("draw", Gtk.Widget.WidgetDrawSignalInfo), '("enterNotifyEvent", Gtk.Widget.WidgetEnterNotifyEventSignalInfo), '("event", Gtk.Widget.WidgetEventSignalInfo), '("eventAfter", Gtk.Widget.WidgetEventAfterSignalInfo), '("focus", Gtk.Widget.WidgetFocusSignalInfo), '("focusInEvent", Gtk.Widget.WidgetFocusInEventSignalInfo), '("focusOutEvent", Gtk.Widget.WidgetFocusOutEventSignalInfo), '("grabBrokenEvent", Gtk.Widget.WidgetGrabBrokenEventSignalInfo), '("grabFocus", Gtk.Widget.WidgetGrabFocusSignalInfo), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("hierarchyChanged", Gtk.Widget.WidgetHierarchyChangedSignalInfo), '("keyPressEvent", Gtk.Widget.WidgetKeyPressEventSignalInfo), '("keyReleaseEvent", Gtk.Widget.WidgetKeyReleaseEventSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("leaveNotifyEvent", Gtk.Widget.WidgetLeaveNotifyEventSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mapEvent", Gtk.Widget.WidgetMapEventSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("motionNotifyEvent", Gtk.Widget.WidgetMotionNotifyEventSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("parentSet", Gtk.Widget.WidgetParentSetSignalInfo), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("propertyNotifyEvent", Gtk.Widget.WidgetPropertyNotifyEventSignalInfo), '("proximityInEvent", Gtk.Widget.WidgetProximityInEventSignalInfo), '("proximityOutEvent", Gtk.Widget.WidgetProximityOutEventSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("remove", Gtk.Container.ContainerRemoveSignalInfo), '("screenChanged", Gtk.Widget.WidgetScreenChangedSignalInfo), '("scrollEvent", Gtk.Widget.WidgetScrollEventSignalInfo), '("selectionClearEvent", Gtk.Widget.WidgetSelectionClearEventSignalInfo), '("selectionGet", Gtk.Widget.WidgetSelectionGetSignalInfo), '("selectionNotifyEvent", Gtk.Widget.WidgetSelectionNotifyEventSignalInfo), '("selectionReceived", Gtk.Widget.WidgetSelectionReceivedSignalInfo), '("selectionRequestEvent", Gtk.Widget.WidgetSelectionRequestEventSignalInfo), '("setFocusChild", Gtk.Container.ContainerSetFocusChildSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("showHelp", Gtk.Widget.WidgetShowHelpSignalInfo), '("sizeAllocate", Gtk.Widget.WidgetSizeAllocateSignalInfo), '("stateChanged", Gtk.Widget.WidgetStateChangedSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleSet", Gtk.Widget.WidgetStyleSetSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("touchEvent", Gtk.Widget.WidgetTouchEventSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unmapEvent", Gtk.Widget.WidgetUnmapEventSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo), '("visibilityNotifyEvent", Gtk.Widget.WidgetVisibilityNotifyEventSignalInfo), '("windowStateEvent", Gtk.Widget.WidgetWindowStateEventSignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method ComboRow::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Handy" , name = "ComboRow" })
-- throws : False
-- Skip return : False

foreign import ccall "hdy_combo_row_new" hdy_combo_row_new :: 
    IO (Ptr ComboRow)

-- | Creates a new @HdyComboRow@.
-- 
-- /Since: 1.0/
comboRowNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m ComboRow
    -- ^ __Returns:__ the newly created @HdyComboRow@
comboRowNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m ComboRow
comboRowNew  = IO ComboRow -> m ComboRow
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ComboRow -> m ComboRow) -> IO ComboRow -> m ComboRow
forall a b. (a -> b) -> a -> b
$ do
    Ptr ComboRow
result <- IO (Ptr ComboRow)
hdy_combo_row_new
    Text -> Ptr ComboRow -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"comboRowNew" Ptr ComboRow
result
    ComboRow
result' <- ((ManagedPtr ComboRow -> ComboRow) -> Ptr ComboRow -> IO ComboRow
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ComboRow -> ComboRow
ComboRow) Ptr ComboRow
result
    ComboRow -> IO ComboRow
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ComboRow
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method ComboRow::bind_model
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "ComboRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a combo row" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "model"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ListModel" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the [iface@Gio.ListModel] to be bound to @self"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "create_list_widget_func"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "ListBoxCreateWidgetFunc" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a function that creates\n  widgets for items to display in the list, or `NULL` in case you also passed\n  `NULL` as @model"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeCall
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "create_current_widget_func"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "ListBoxCreateWidgetFunc" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a function that creates\n  widgets for items to display as the selected item, or `NULL` in case you\n  also passed `NULL` as @model"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 4
--           , argDestroy = 5
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "user data passed to @create_list_widget_func and\n  @create_current_widget_func"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data_free_func"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "function for freeing @user_data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "hdy_combo_row_bind_model" hdy_combo_row_bind_model :: 
    Ptr ComboRow ->                         -- self : TInterface (Name {namespace = "Handy", name = "ComboRow"})
    Ptr Gio.ListModel.ListModel ->          -- model : TInterface (Name {namespace = "Gio", name = "ListModel"})
    FunPtr Gtk.Callbacks.C_ListBoxCreateWidgetFunc -> -- create_list_widget_func : TInterface (Name {namespace = "Gtk", name = "ListBoxCreateWidgetFunc"})
    FunPtr Gtk.Callbacks.C_ListBoxCreateWidgetFunc -> -- create_current_widget_func : TInterface (Name {namespace = "Gtk", name = "ListBoxCreateWidgetFunc"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- user_data_free_func : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO ()

-- | Binds /@model@/ to /@self@/.
-- 
-- If /@self@/ was already bound to a model, that previous binding is destroyed.
-- 
-- The contents of /@self@/ are cleared and then filled with widgets that represent
-- items from /@model@/. /@self@/ is updated whenever /@model@/ changes. If /@model@/ is
-- @NULL@, /@self@/ is left empty.
-- 
-- /Since: 1.0/
comboRowBindModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsComboRow a, Gio.ListModel.IsListModel b) =>
    a
    -- ^ /@self@/: a combo row
    -> Maybe (b)
    -- ^ /@model@/: the t'GI.Gio.Interfaces.ListModel.ListModel' to be bound to /@self@/
    -> Maybe (Gtk.Callbacks.ListBoxCreateWidgetFunc)
    -- ^ /@createListWidgetFunc@/: a function that creates
    --   widgets for items to display in the list, or @NULL@ in case you also passed
    --   @NULL@ as /@model@/
    -> Maybe (Gtk.Callbacks.ListBoxCreateWidgetFunc)
    -- ^ /@createCurrentWidgetFunc@/: a function that creates
    --   widgets for items to display as the selected item, or @NULL@ in case you
    --   also passed @NULL@ as /@model@/
    -> m ()
comboRowBindModel :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsComboRow a, IsListModel b) =>
a
-> Maybe b
-> Maybe ListBoxCreateWidgetFunc
-> Maybe ListBoxCreateWidgetFunc
-> m ()
comboRowBindModel a
self Maybe b
model Maybe ListBoxCreateWidgetFunc
createListWidgetFunc Maybe ListBoxCreateWidgetFunc
createCurrentWidgetFunc = 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 ComboRow
self' <- a -> IO (Ptr ComboRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr ListModel
maybeModel <- case Maybe b
model of
        Maybe b
Nothing -> Ptr ListModel -> IO (Ptr ListModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ListModel
forall a. Ptr a
nullPtr
        Just b
jModel -> do
            Ptr ListModel
jModel' <- b -> IO (Ptr ListModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jModel
            Ptr ListModel -> IO (Ptr ListModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ListModel
jModel'
    FunPtr C_ListBoxCreateWidgetFunc
maybeCreateListWidgetFunc <- case Maybe ListBoxCreateWidgetFunc
createListWidgetFunc of
        Maybe ListBoxCreateWidgetFunc
Nothing -> FunPtr C_ListBoxCreateWidgetFunc
-> IO (FunPtr C_ListBoxCreateWidgetFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_ListBoxCreateWidgetFunc
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just ListBoxCreateWidgetFunc
jCreateListWidgetFunc -> do
            FunPtr C_ListBoxCreateWidgetFunc
jCreateListWidgetFunc' <- C_ListBoxCreateWidgetFunc -> IO (FunPtr C_ListBoxCreateWidgetFunc)
Gtk.Callbacks.mk_ListBoxCreateWidgetFunc (Maybe (Ptr (FunPtr C_ListBoxCreateWidgetFunc))
-> ListBoxCreateWidgetFunc_WithClosures
-> C_ListBoxCreateWidgetFunc
Gtk.Callbacks.wrap_ListBoxCreateWidgetFunc Maybe (Ptr (FunPtr C_ListBoxCreateWidgetFunc))
forall a. Maybe a
Nothing (ListBoxCreateWidgetFunc -> ListBoxCreateWidgetFunc_WithClosures
Gtk.Callbacks.drop_closures_ListBoxCreateWidgetFunc ListBoxCreateWidgetFunc
jCreateListWidgetFunc))
            FunPtr C_ListBoxCreateWidgetFunc
-> IO (FunPtr C_ListBoxCreateWidgetFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_ListBoxCreateWidgetFunc
jCreateListWidgetFunc'
    FunPtr C_ListBoxCreateWidgetFunc
maybeCreateCurrentWidgetFunc <- case Maybe ListBoxCreateWidgetFunc
createCurrentWidgetFunc of
        Maybe ListBoxCreateWidgetFunc
Nothing -> FunPtr C_ListBoxCreateWidgetFunc
-> IO (FunPtr C_ListBoxCreateWidgetFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_ListBoxCreateWidgetFunc
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just ListBoxCreateWidgetFunc
jCreateCurrentWidgetFunc -> do
            FunPtr C_ListBoxCreateWidgetFunc
jCreateCurrentWidgetFunc' <- C_ListBoxCreateWidgetFunc -> IO (FunPtr C_ListBoxCreateWidgetFunc)
Gtk.Callbacks.mk_ListBoxCreateWidgetFunc (Maybe (Ptr (FunPtr C_ListBoxCreateWidgetFunc))
-> ListBoxCreateWidgetFunc_WithClosures
-> C_ListBoxCreateWidgetFunc
Gtk.Callbacks.wrap_ListBoxCreateWidgetFunc Maybe (Ptr (FunPtr C_ListBoxCreateWidgetFunc))
forall a. Maybe a
Nothing (ListBoxCreateWidgetFunc -> ListBoxCreateWidgetFunc_WithClosures
Gtk.Callbacks.drop_closures_ListBoxCreateWidgetFunc ListBoxCreateWidgetFunc
jCreateCurrentWidgetFunc))
            FunPtr C_ListBoxCreateWidgetFunc
-> IO (FunPtr C_ListBoxCreateWidgetFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_ListBoxCreateWidgetFunc
jCreateCurrentWidgetFunc'
    let userData :: Ptr ()
userData = FunPtr C_ListBoxCreateWidgetFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_ListBoxCreateWidgetFunc
maybeCreateCurrentWidgetFunc
    let userDataFreeFunc :: FunPtr (Ptr a -> IO ())
userDataFreeFunc = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    Ptr ComboRow
-> Ptr ListModel
-> FunPtr C_ListBoxCreateWidgetFunc
-> FunPtr C_ListBoxCreateWidgetFunc
-> Ptr ()
-> FunPtr C_DestroyNotify
-> IO ()
hdy_combo_row_bind_model Ptr ComboRow
self' Ptr ListModel
maybeModel FunPtr C_ListBoxCreateWidgetFunc
maybeCreateListWidgetFunc FunPtr C_ListBoxCreateWidgetFunc
maybeCreateCurrentWidgetFunc Ptr ()
userData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
userDataFreeFunc
    Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_ListBoxCreateWidgetFunc -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_ListBoxCreateWidgetFunc
maybeCreateListWidgetFunc
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
model b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ComboRowBindModelMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (Gtk.Callbacks.ListBoxCreateWidgetFunc) -> Maybe (Gtk.Callbacks.ListBoxCreateWidgetFunc) -> m ()), MonadIO m, IsComboRow a, Gio.ListModel.IsListModel b) => O.OverloadedMethod ComboRowBindModelMethodInfo a signature where
    overloadedMethod = comboRowBindModel

instance O.OverloadedMethodInfo ComboRowBindModelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.ComboRow.comboRowBindModel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.4/docs/GI-Handy-Objects-ComboRow.html#v:comboRowBindModel"
        })


#endif

-- method ComboRow::bind_name_model
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "ComboRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a combo row" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "model"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ListModel" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the [iface@Gio.ListModel] to be bound to @self"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "get_name_func"
--           , argType =
--               TInterface
--                 Name { namespace = "Handy" , name = "ComboRowGetNameFunc" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a function that creates names for items, or\n  `NULL` in case you also passed `NULL` as @model"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 3
--           , argDestroy = 4
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data passed to @get_name_func"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data_free_func"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "function for freeing @user_data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "hdy_combo_row_bind_name_model" hdy_combo_row_bind_name_model :: 
    Ptr ComboRow ->                         -- self : TInterface (Name {namespace = "Handy", name = "ComboRow"})
    Ptr Gio.ListModel.ListModel ->          -- model : TInterface (Name {namespace = "Gio", name = "ListModel"})
    FunPtr Handy.Callbacks.C_ComboRowGetNameFunc -> -- get_name_func : TInterface (Name {namespace = "Handy", name = "ComboRowGetNameFunc"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- user_data_free_func : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO ()

-- | Binds /@model@/ to /@self@/.
-- 
-- If /@self@/ was already bound to a model, that previous binding is destroyed.
-- 
-- The contents of /@self@/ are cleared and then filled with widgets that represent
-- items from /@model@/. /@self@/ is updated whenever /@model@/ changes. If /@model@/ is
-- @NULL@, /@self@/ is left empty.
-- 
-- This is more convenient to use than [method/@comboRow@/.bind_model] if you want
-- to represent items of the model with names.
-- 
-- /Since: 1.0/
comboRowBindNameModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsComboRow a, Gio.ListModel.IsListModel b) =>
    a
    -- ^ /@self@/: a combo row
    -> Maybe (b)
    -- ^ /@model@/: the t'GI.Gio.Interfaces.ListModel.ListModel' to be bound to /@self@/
    -> Maybe (Handy.Callbacks.ComboRowGetNameFunc)
    -- ^ /@getNameFunc@/: a function that creates names for items, or
    --   @NULL@ in case you also passed @NULL@ as /@model@/
    -> m ()
comboRowBindNameModel :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsComboRow a, IsListModel b) =>
a -> Maybe b -> Maybe ComboRowGetNameFunc -> m ()
comboRowBindNameModel a
self Maybe b
model Maybe ComboRowGetNameFunc
getNameFunc = 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 ComboRow
self' <- a -> IO (Ptr ComboRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr ListModel
maybeModel <- case Maybe b
model of
        Maybe b
Nothing -> Ptr ListModel -> IO (Ptr ListModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ListModel
forall a. Ptr a
nullPtr
        Just b
jModel -> do
            Ptr ListModel
jModel' <- b -> IO (Ptr ListModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jModel
            Ptr ListModel -> IO (Ptr ListModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ListModel
jModel'
    FunPtr C_ComboRowGetNameFunc
maybeGetNameFunc <- case Maybe ComboRowGetNameFunc
getNameFunc of
        Maybe ComboRowGetNameFunc
Nothing -> FunPtr C_ComboRowGetNameFunc -> IO (FunPtr C_ComboRowGetNameFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_ComboRowGetNameFunc
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just ComboRowGetNameFunc
jGetNameFunc -> do
            FunPtr C_ComboRowGetNameFunc
jGetNameFunc' <- C_ComboRowGetNameFunc -> IO (FunPtr C_ComboRowGetNameFunc)
Handy.Callbacks.mk_ComboRowGetNameFunc (Maybe (Ptr (FunPtr C_ComboRowGetNameFunc))
-> ComboRowGetNameFunc_WithClosures -> C_ComboRowGetNameFunc
Handy.Callbacks.wrap_ComboRowGetNameFunc Maybe (Ptr (FunPtr C_ComboRowGetNameFunc))
forall a. Maybe a
Nothing (ComboRowGetNameFunc -> ComboRowGetNameFunc_WithClosures
Handy.Callbacks.drop_closures_ComboRowGetNameFunc ComboRowGetNameFunc
jGetNameFunc))
            FunPtr C_ComboRowGetNameFunc -> IO (FunPtr C_ComboRowGetNameFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_ComboRowGetNameFunc
jGetNameFunc'
    let userData :: Ptr ()
userData = FunPtr C_ComboRowGetNameFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_ComboRowGetNameFunc
maybeGetNameFunc
    let userDataFreeFunc :: FunPtr (Ptr a -> IO ())
userDataFreeFunc = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    Ptr ComboRow
-> Ptr ListModel
-> FunPtr C_ComboRowGetNameFunc
-> Ptr ()
-> FunPtr C_DestroyNotify
-> IO ()
hdy_combo_row_bind_name_model Ptr ComboRow
self' Ptr ListModel
maybeModel FunPtr C_ComboRowGetNameFunc
maybeGetNameFunc Ptr ()
userData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
userDataFreeFunc
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
model b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ComboRowBindNameModelMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (Handy.Callbacks.ComboRowGetNameFunc) -> m ()), MonadIO m, IsComboRow a, Gio.ListModel.IsListModel b) => O.OverloadedMethod ComboRowBindNameModelMethodInfo a signature where
    overloadedMethod = comboRowBindNameModel

instance O.OverloadedMethodInfo ComboRowBindNameModelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.ComboRow.comboRowBindNameModel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.4/docs/GI-Handy-Objects-ComboRow.html#v:comboRowBindNameModel"
        })


#endif

-- method ComboRow::get_model
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "ComboRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a combo row" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "ListModel" })
-- throws : False
-- Skip return : False

foreign import ccall "hdy_combo_row_get_model" hdy_combo_row_get_model :: 
    Ptr ComboRow ->                         -- self : TInterface (Name {namespace = "Handy", name = "ComboRow"})
    IO (Ptr Gio.ListModel.ListModel)

-- | Gets the model bound to /@self@/.
-- 
-- /Since: 1.0/
comboRowGetModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsComboRow a) =>
    a
    -- ^ /@self@/: a combo row
    -> m (Maybe Gio.ListModel.ListModel)
    -- ^ __Returns:__ the t'GI.Gio.Interfaces.ListModel.ListModel' bound to /@self@/
comboRowGetModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComboRow a) =>
a -> m (Maybe ListModel)
comboRowGetModel a
self = IO (Maybe ListModel) -> m (Maybe ListModel)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ListModel) -> m (Maybe ListModel))
-> IO (Maybe ListModel) -> m (Maybe ListModel)
forall a b. (a -> b) -> a -> b
$ do
    Ptr ComboRow
self' <- a -> IO (Ptr ComboRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr ListModel
result <- Ptr ComboRow -> IO (Ptr ListModel)
hdy_combo_row_get_model Ptr ComboRow
self'
    Maybe ListModel
maybeResult <- Ptr ListModel
-> (Ptr ListModel -> IO ListModel) -> IO (Maybe ListModel)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr ListModel
result ((Ptr ListModel -> IO ListModel) -> IO (Maybe ListModel))
-> (Ptr ListModel -> IO ListModel) -> IO (Maybe ListModel)
forall a b. (a -> b) -> a -> b
$ \Ptr ListModel
result' -> do
        ListModel
result'' <- ((ManagedPtr ListModel -> ListModel)
-> Ptr ListModel -> IO ListModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ListModel -> ListModel
Gio.ListModel.ListModel) Ptr ListModel
result'
        ListModel -> IO ListModel
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ListModel
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe ListModel -> IO (Maybe ListModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ListModel
maybeResult

#if defined(ENABLE_OVERLOADING)
data ComboRowGetModelMethodInfo
instance (signature ~ (m (Maybe Gio.ListModel.ListModel)), MonadIO m, IsComboRow a) => O.OverloadedMethod ComboRowGetModelMethodInfo a signature where
    overloadedMethod = comboRowGetModel

instance O.OverloadedMethodInfo ComboRowGetModelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.ComboRow.comboRowGetModel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.4/docs/GI-Handy-Objects-ComboRow.html#v:comboRowGetModel"
        })


#endif

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

foreign import ccall "hdy_combo_row_get_selected_index" hdy_combo_row_get_selected_index :: 
    Ptr ComboRow ->                         -- self : TInterface (Name {namespace = "Handy", name = "ComboRow"})
    IO Int32

-- | Gets the index of the selected item in its t'GI.Gio.Interfaces.ListModel.ListModel'.
-- 
-- /Since: 1.0/
comboRowGetSelectedIndex ::
    (B.CallStack.HasCallStack, MonadIO m, IsComboRow a) =>
    a
    -- ^ /@self@/: a combo row
    -> m Int32
    -- ^ __Returns:__ the index of the selected item, or -1 if no item is selected
comboRowGetSelectedIndex :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComboRow a) =>
a -> m Int32
comboRowGetSelectedIndex a
self = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr ComboRow
self' <- a -> IO (Ptr ComboRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Int32
result <- Ptr ComboRow -> IO Int32
hdy_combo_row_get_selected_index Ptr ComboRow
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data ComboRowGetSelectedIndexMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsComboRow a) => O.OverloadedMethod ComboRowGetSelectedIndexMethodInfo a signature where
    overloadedMethod = comboRowGetSelectedIndex

instance O.OverloadedMethodInfo ComboRowGetSelectedIndexMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.ComboRow.comboRowGetSelectedIndex",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.4/docs/GI-Handy-Objects-ComboRow.html#v:comboRowGetSelectedIndex"
        })


#endif

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

foreign import ccall "hdy_combo_row_get_use_subtitle" hdy_combo_row_get_use_subtitle :: 
    Ptr ComboRow ->                         -- self : TInterface (Name {namespace = "Handy", name = "ComboRow"})
    IO CInt

-- | Gets whether the current value of /@self@/ should be displayed as its subtitle.
-- 
-- /Since: 1.0/
comboRowGetUseSubtitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsComboRow a) =>
    a
    -- ^ /@self@/: a combo row
    -> m Bool
    -- ^ __Returns:__ whether the current value of /@self@/ should be displayed as its
    --   subtitle
comboRowGetUseSubtitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComboRow a) =>
a -> m Bool
comboRowGetUseSubtitle a
self = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr ComboRow
self' <- a -> IO (Ptr ComboRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr ComboRow -> IO CInt
hdy_combo_row_get_use_subtitle Ptr ComboRow
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ComboRowGetUseSubtitleMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsComboRow a) => O.OverloadedMethod ComboRowGetUseSubtitleMethodInfo a signature where
    overloadedMethod = comboRowGetUseSubtitle

instance O.OverloadedMethodInfo ComboRowGetUseSubtitleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.ComboRow.comboRowGetUseSubtitle",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.4/docs/GI-Handy-Objects-ComboRow.html#v:comboRowGetUseSubtitle"
        })


#endif

-- method ComboRow::set_for_enum
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "ComboRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a combo row" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "enum_type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the enumeration [alias@GLib.Type] to be bound to @self"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "get_name_func"
--           , argType =
--               TInterface
--                 Name
--                   { namespace = "Handy" , name = "ComboRowGetEnumValueNameFunc" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a function that creates names for items, or\n  `NULL` in case you also passed `NULL` as @model"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 3
--           , argDestroy = 4
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data passed to @get_name_func"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data_free_func"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "function for freeing @user_data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "hdy_combo_row_set_for_enum" hdy_combo_row_set_for_enum :: 
    Ptr ComboRow ->                         -- self : TInterface (Name {namespace = "Handy", name = "ComboRow"})
    CGType ->                               -- enum_type : TBasicType TGType
    FunPtr Handy.Callbacks.C_ComboRowGetEnumValueNameFunc -> -- get_name_func : TInterface (Name {namespace = "Handy", name = "ComboRowGetEnumValueNameFunc"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- user_data_free_func : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO ()

-- | Creates a model for /@enumType@/ and binds it to /@self@/.
-- 
-- The items of the model will be [class/@enumValueObject@/] objects.
-- 
-- If /@self@/ was already bound to a model, that previous binding is destroyed.
-- 
-- The contents of /@self@/ are cleared and then filled with widgets that represent
-- items from /@model@/. /@self@/ is updated whenever /@model@/ changes. If /@model@/ is
-- @NULL@, /@self@/ is left empty.
-- 
-- This is more convenient to use than [method/@comboRow@/.bind_name_model] if you
-- want to represent values of an enumeration with names.
-- 
-- See [func/@enumValueRowName@/].
-- 
-- /Since: 1.0/
comboRowSetForEnum ::
    (B.CallStack.HasCallStack, MonadIO m, IsComboRow a) =>
    a
    -- ^ /@self@/: a combo row
    -> GType
    -- ^ /@enumType@/: the enumeration [alias/@gLib@/.Type] to be bound to /@self@/
    -> Maybe (Handy.Callbacks.ComboRowGetEnumValueNameFunc)
    -- ^ /@getNameFunc@/: a function that creates names for items, or
    --   @NULL@ in case you also passed @NULL@ as /@model@/
    -> m ()
comboRowSetForEnum :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComboRow a) =>
a -> GType -> Maybe ComboRowGetEnumValueNameFunc -> m ()
comboRowSetForEnum a
self GType
enumType Maybe ComboRowGetEnumValueNameFunc
getNameFunc = 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 ComboRow
self' <- a -> IO (Ptr ComboRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let enumType' :: CGType
enumType' = GType -> CGType
gtypeToCGType GType
enumType
    FunPtr C_ComboRowGetEnumValueNameFunc
maybeGetNameFunc <- case Maybe ComboRowGetEnumValueNameFunc
getNameFunc of
        Maybe ComboRowGetEnumValueNameFunc
Nothing -> FunPtr C_ComboRowGetEnumValueNameFunc
-> IO (FunPtr C_ComboRowGetEnumValueNameFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_ComboRowGetEnumValueNameFunc
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just ComboRowGetEnumValueNameFunc
jGetNameFunc -> do
            FunPtr C_ComboRowGetEnumValueNameFunc
jGetNameFunc' <- C_ComboRowGetEnumValueNameFunc
-> IO (FunPtr C_ComboRowGetEnumValueNameFunc)
Handy.Callbacks.mk_ComboRowGetEnumValueNameFunc (Maybe (Ptr (FunPtr C_ComboRowGetEnumValueNameFunc))
-> ComboRowGetEnumValueNameFunc_WithClosures
-> C_ComboRowGetEnumValueNameFunc
Handy.Callbacks.wrap_ComboRowGetEnumValueNameFunc Maybe (Ptr (FunPtr C_ComboRowGetEnumValueNameFunc))
forall a. Maybe a
Nothing (ComboRowGetEnumValueNameFunc
-> ComboRowGetEnumValueNameFunc_WithClosures
Handy.Callbacks.drop_closures_ComboRowGetEnumValueNameFunc ComboRowGetEnumValueNameFunc
jGetNameFunc))
            FunPtr C_ComboRowGetEnumValueNameFunc
-> IO (FunPtr C_ComboRowGetEnumValueNameFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_ComboRowGetEnumValueNameFunc
jGetNameFunc'
    let userData :: Ptr ()
userData = FunPtr C_ComboRowGetEnumValueNameFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_ComboRowGetEnumValueNameFunc
maybeGetNameFunc
    let userDataFreeFunc :: FunPtr (Ptr a -> IO ())
userDataFreeFunc = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    Ptr ComboRow
-> CGType
-> FunPtr C_ComboRowGetEnumValueNameFunc
-> Ptr ()
-> FunPtr C_DestroyNotify
-> IO ()
hdy_combo_row_set_for_enum Ptr ComboRow
self' CGType
enumType' FunPtr C_ComboRowGetEnumValueNameFunc
maybeGetNameFunc Ptr ()
userData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
userDataFreeFunc
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ComboRowSetForEnumMethodInfo
instance (signature ~ (GType -> Maybe (Handy.Callbacks.ComboRowGetEnumValueNameFunc) -> m ()), MonadIO m, IsComboRow a) => O.OverloadedMethod ComboRowSetForEnumMethodInfo a signature where
    overloadedMethod = comboRowSetForEnum

instance O.OverloadedMethodInfo ComboRowSetForEnumMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.ComboRow.comboRowSetForEnum",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.4/docs/GI-Handy-Objects-ComboRow.html#v:comboRowSetForEnum"
        })


#endif

-- method ComboRow::set_get_name_func
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "ComboRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a combo row" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "get_name_func"
--           , argType =
--               TInterface
--                 Name { namespace = "Handy" , name = "ComboRowGetNameFunc" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a function that creates names for items, or\n  `NULL` in case you also passed `NULL` as @model"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 2
--           , argDestroy = 3
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data passed to @get_name_func"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data_free_func"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "function for freeing @user_data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "hdy_combo_row_set_get_name_func" hdy_combo_row_set_get_name_func :: 
    Ptr ComboRow ->                         -- self : TInterface (Name {namespace = "Handy", name = "ComboRow"})
    FunPtr Handy.Callbacks.C_ComboRowGetNameFunc -> -- get_name_func : TInterface (Name {namespace = "Handy", name = "ComboRowGetNameFunc"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- user_data_free_func : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO ()

-- | Sets a closure to convert items into names.
-- 
-- See [property/@comboRow@/:use-subtitle].
-- 
-- /Since: 1.0/
comboRowSetGetNameFunc ::
    (B.CallStack.HasCallStack, MonadIO m, IsComboRow a) =>
    a
    -- ^ /@self@/: a combo row
    -> Maybe (Handy.Callbacks.ComboRowGetNameFunc)
    -- ^ /@getNameFunc@/: a function that creates names for items, or
    --   @NULL@ in case you also passed @NULL@ as /@model@/
    -> m ()
comboRowSetGetNameFunc :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComboRow a) =>
a -> Maybe ComboRowGetNameFunc -> m ()
comboRowSetGetNameFunc a
self Maybe ComboRowGetNameFunc
getNameFunc = 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 ComboRow
self' <- a -> IO (Ptr ComboRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    FunPtr C_ComboRowGetNameFunc
maybeGetNameFunc <- case Maybe ComboRowGetNameFunc
getNameFunc of
        Maybe ComboRowGetNameFunc
Nothing -> FunPtr C_ComboRowGetNameFunc -> IO (FunPtr C_ComboRowGetNameFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_ComboRowGetNameFunc
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just ComboRowGetNameFunc
jGetNameFunc -> do
            FunPtr C_ComboRowGetNameFunc
jGetNameFunc' <- C_ComboRowGetNameFunc -> IO (FunPtr C_ComboRowGetNameFunc)
Handy.Callbacks.mk_ComboRowGetNameFunc (Maybe (Ptr (FunPtr C_ComboRowGetNameFunc))
-> ComboRowGetNameFunc_WithClosures -> C_ComboRowGetNameFunc
Handy.Callbacks.wrap_ComboRowGetNameFunc Maybe (Ptr (FunPtr C_ComboRowGetNameFunc))
forall a. Maybe a
Nothing (ComboRowGetNameFunc -> ComboRowGetNameFunc_WithClosures
Handy.Callbacks.drop_closures_ComboRowGetNameFunc ComboRowGetNameFunc
jGetNameFunc))
            FunPtr C_ComboRowGetNameFunc -> IO (FunPtr C_ComboRowGetNameFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_ComboRowGetNameFunc
jGetNameFunc'
    let userData :: Ptr ()
userData = FunPtr C_ComboRowGetNameFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_ComboRowGetNameFunc
maybeGetNameFunc
    let userDataFreeFunc :: FunPtr (Ptr a -> IO ())
userDataFreeFunc = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    Ptr ComboRow
-> FunPtr C_ComboRowGetNameFunc
-> Ptr ()
-> FunPtr C_DestroyNotify
-> IO ()
hdy_combo_row_set_get_name_func Ptr ComboRow
self' FunPtr C_ComboRowGetNameFunc
maybeGetNameFunc Ptr ()
userData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
userDataFreeFunc
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ComboRowSetGetNameFuncMethodInfo
instance (signature ~ (Maybe (Handy.Callbacks.ComboRowGetNameFunc) -> m ()), MonadIO m, IsComboRow a) => O.OverloadedMethod ComboRowSetGetNameFuncMethodInfo a signature where
    overloadedMethod = comboRowSetGetNameFunc

instance O.OverloadedMethodInfo ComboRowSetGetNameFuncMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.ComboRow.comboRowSetGetNameFunc",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.4/docs/GI-Handy-Objects-ComboRow.html#v:comboRowSetGetNameFunc"
        })


#endif

-- method ComboRow::set_selected_index
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "ComboRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a combo row" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "selected_index"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the index of the selected item"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "hdy_combo_row_set_selected_index" hdy_combo_row_set_selected_index :: 
    Ptr ComboRow ->                         -- self : TInterface (Name {namespace = "Handy", name = "ComboRow"})
    Int32 ->                                -- selected_index : TBasicType TInt
    IO ()

-- | Sets the index of the selected item in its t'GI.Gio.Interfaces.ListModel.ListModel'.
-- 
-- /Since: 1.0/
comboRowSetSelectedIndex ::
    (B.CallStack.HasCallStack, MonadIO m, IsComboRow a) =>
    a
    -- ^ /@self@/: a combo row
    -> Int32
    -- ^ /@selectedIndex@/: the index of the selected item
    -> m ()
comboRowSetSelectedIndex :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComboRow a) =>
a -> Int32 -> m ()
comboRowSetSelectedIndex a
self Int32
selectedIndex = 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 ComboRow
self' <- a -> IO (Ptr ComboRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr ComboRow -> Int32 -> IO ()
hdy_combo_row_set_selected_index Ptr ComboRow
self' Int32
selectedIndex
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ComboRowSetSelectedIndexMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsComboRow a) => O.OverloadedMethod ComboRowSetSelectedIndexMethodInfo a signature where
    overloadedMethod = comboRowSetSelectedIndex

instance O.OverloadedMethodInfo ComboRowSetSelectedIndexMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.ComboRow.comboRowSetSelectedIndex",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.4/docs/GI-Handy-Objects-ComboRow.html#v:comboRowSetSelectedIndex"
        })


#endif

-- method ComboRow::set_use_subtitle
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "ComboRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a combo row" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "use_subtitle"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "`TRUE` to set the current value as the subtitle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "hdy_combo_row_set_use_subtitle" hdy_combo_row_set_use_subtitle :: 
    Ptr ComboRow ->                         -- self : TInterface (Name {namespace = "Handy", name = "ComboRow"})
    CInt ->                                 -- use_subtitle : TBasicType TBoolean
    IO ()

-- | Sets whether the current value of /@self@/ should be displayed as its subtitle.
-- 
-- If @TRUE@, you should not access [property/@actionRow@/:subtitle].
-- 
-- /Since: 1.0/
comboRowSetUseSubtitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsComboRow a) =>
    a
    -- ^ /@self@/: a combo row
    -> Bool
    -- ^ /@useSubtitle@/: @TRUE@ to set the current value as the subtitle
    -> m ()
comboRowSetUseSubtitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComboRow a) =>
a -> Bool -> m ()
comboRowSetUseSubtitle a
self Bool
useSubtitle = 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 ComboRow
self' <- a -> IO (Ptr ComboRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let useSubtitle' :: CInt
useSubtitle' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
useSubtitle
    Ptr ComboRow -> CInt -> IO ()
hdy_combo_row_set_use_subtitle Ptr ComboRow
self' CInt
useSubtitle'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ComboRowSetUseSubtitleMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsComboRow a) => O.OverloadedMethod ComboRowSetUseSubtitleMethodInfo a signature where
    overloadedMethod = comboRowSetUseSubtitle

instance O.OverloadedMethodInfo ComboRowSetUseSubtitleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.ComboRow.comboRowSetUseSubtitle",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.4/docs/GI-Handy-Objects-ComboRow.html#v:comboRowSetUseSubtitle"
        })


#endif