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


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @GtkToggleButton@ is a button which remains “pressed-in” when
-- clicked.
-- 
-- Clicking again will cause the toggle button to return to its normal state.
-- 
-- A toggle button is created by calling either 'GI.Gtk.Objects.ToggleButton.toggleButtonNew' or
-- 'GI.Gtk.Objects.ToggleButton.toggleButtonNewWithLabel'. If using the former, it is advisable
-- to pack a widget, (such as a @GtkLabel@ and\/or a @GtkImage@), into the toggle
-- button’s container. (See t'GI.Gtk.Objects.Button.Button' for more information).
-- 
-- The state of a @GtkToggleButton@ can be set specifically using
-- 'GI.Gtk.Objects.ToggleButton.toggleButtonSetActive', and retrieved using
-- 'GI.Gtk.Objects.ToggleButton.toggleButtonGetActive'.
-- 
-- To simply switch the state of a toggle button, use
-- 'GI.Gtk.Objects.ToggleButton.toggleButtonToggled'.
-- 
-- = Grouping
-- 
-- Toggle buttons can be grouped together, to form mutually exclusive
-- groups - only one of the buttons can be toggled at a time, and toggling
-- another one will switch the currently toggled one off.
-- 
-- To add a @GtkToggleButton@ to a group, use 'GI.Gtk.Objects.ToggleButton.toggleButtonSetGroup'.
-- 
-- = CSS nodes
-- 
-- @GtkToggleButton@ has a single CSS node with name button. To differentiate
-- it from a plain @GtkButton@, it gets the .toggle style class.
-- 
-- == Creating two @GtkToggleButton@ widgets.
-- 
-- 
-- === /c code/
-- >static void output_state (GtkToggleButton *source, gpointer user_data)
-- >{
-- >  printf ("Active: %d\n", gtk_toggle_button_get_active (source));
-- >}
-- >
-- >void make_toggles (void)
-- >{
-- >  GtkWidget *window, *toggle1, *toggle2;
-- >  GtkWidget *box;
-- >  const char *text;
-- >
-- >  window = gtk_window_new ();
-- >  box = gtk_box_new (GTK_ORIENTATION_VERTICAL, 12);
-- >
-- >  text = "Hi, I’m a toggle button.";
-- >  toggle1 = gtk_toggle_button_new_with_label (text);
-- >
-- >  g_signal_connect (toggle1, "toggled",
-- >                    G_CALLBACK (output_state),
-- >                    NULL);
-- >  gtk_box_append (GTK_BOX (box), toggle1);
-- >
-- >  text = "Hi, I’m a toggle button.";
-- >  toggle2 = gtk_toggle_button_new_with_label (text);
-- >  g_signal_connect (toggle2, "toggled",
-- >                    G_CALLBACK (output_state),
-- >                    NULL);
-- >  gtk_box_append (GTK_BOX (box), toggle2);
-- >
-- >  gtk_window_set_child (GTK_WINDOW (window), box);
-- >  gtk_widget_show (window);
-- >}
-- 

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

module GI.Gtk.Objects.ToggleButton
    ( 

-- * Exported types
    ToggleButton(..)                        ,
    IsToggleButton                          ,
    toToggleButton                          ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [actionSetEnabled]("GI.Gtk.Objects.Widget#g:method:actionSetEnabled"), [activate]("GI.Gtk.Objects.Widget#g:method:activate"), [activateAction]("GI.Gtk.Objects.Widget#g:method:activateAction"), [activateDefault]("GI.Gtk.Objects.Widget#g:method:activateDefault"), [addController]("GI.Gtk.Objects.Widget#g:method:addController"), [addCssClass]("GI.Gtk.Objects.Widget#g:method:addCssClass"), [addMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:addMnemonicLabel"), [addTickCallback]("GI.Gtk.Objects.Widget#g:method:addTickCallback"), [allocate]("GI.Gtk.Objects.Widget#g:method:allocate"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [childFocus]("GI.Gtk.Objects.Widget#g:method:childFocus"), [computeBounds]("GI.Gtk.Objects.Widget#g:method:computeBounds"), [computeExpand]("GI.Gtk.Objects.Widget#g:method:computeExpand"), [computePoint]("GI.Gtk.Objects.Widget#g:method:computePoint"), [computeTransform]("GI.Gtk.Objects.Widget#g:method:computeTransform"), [contains]("GI.Gtk.Objects.Widget#g:method:contains"), [createPangoContext]("GI.Gtk.Objects.Widget#g:method:createPangoContext"), [createPangoLayout]("GI.Gtk.Objects.Widget#g:method:createPangoLayout"), [dragCheckThreshold]("GI.Gtk.Objects.Widget#g:method:dragCheckThreshold"), [errorBell]("GI.Gtk.Objects.Widget#g:method:errorBell"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [grabFocus]("GI.Gtk.Objects.Widget#g:method:grabFocus"), [hasCssClass]("GI.Gtk.Objects.Widget#g:method:hasCssClass"), [hasDefault]("GI.Gtk.Objects.Widget#g:method:hasDefault"), [hasFocus]("GI.Gtk.Objects.Widget#g:method:hasFocus"), [hasVisibleFocus]("GI.Gtk.Objects.Widget#g:method:hasVisibleFocus"), [hide]("GI.Gtk.Objects.Widget#g:method:hide"), [inDestruction]("GI.Gtk.Objects.Widget#g:method:inDestruction"), [initTemplate]("GI.Gtk.Objects.Widget#g:method:initTemplate"), [insertActionGroup]("GI.Gtk.Objects.Widget#g:method:insertActionGroup"), [insertAfter]("GI.Gtk.Objects.Widget#g:method:insertAfter"), [insertBefore]("GI.Gtk.Objects.Widget#g:method:insertBefore"), [isAncestor]("GI.Gtk.Objects.Widget#g:method:isAncestor"), [isDrawable]("GI.Gtk.Objects.Widget#g:method:isDrawable"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isFocus]("GI.Gtk.Objects.Widget#g:method:isFocus"), [isSensitive]("GI.Gtk.Objects.Widget#g:method:isSensitive"), [isVisible]("GI.Gtk.Objects.Widget#g:method:isVisible"), [keynavFailed]("GI.Gtk.Objects.Widget#g:method:keynavFailed"), [listMnemonicLabels]("GI.Gtk.Objects.Widget#g:method:listMnemonicLabels"), [map]("GI.Gtk.Objects.Widget#g:method:map"), [measure]("GI.Gtk.Objects.Widget#g:method:measure"), [mnemonicActivate]("GI.Gtk.Objects.Widget#g:method:mnemonicActivate"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [observeChildren]("GI.Gtk.Objects.Widget#g:method:observeChildren"), [observeControllers]("GI.Gtk.Objects.Widget#g:method:observeControllers"), [pick]("GI.Gtk.Objects.Widget#g:method:pick"), [queueAllocate]("GI.Gtk.Objects.Widget#g:method:queueAllocate"), [queueDraw]("GI.Gtk.Objects.Widget#g:method:queueDraw"), [queueResize]("GI.Gtk.Objects.Widget#g:method:queueResize"), [realize]("GI.Gtk.Objects.Widget#g:method:realize"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeController]("GI.Gtk.Objects.Widget#g:method:removeController"), [removeCssClass]("GI.Gtk.Objects.Widget#g:method:removeCssClass"), [removeMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:removeMnemonicLabel"), [removeTickCallback]("GI.Gtk.Objects.Widget#g:method:removeTickCallback"), [resetProperty]("GI.Gtk.Interfaces.Accessible#g:method:resetProperty"), [resetRelation]("GI.Gtk.Interfaces.Accessible#g:method:resetRelation"), [resetState]("GI.Gtk.Interfaces.Accessible#g:method:resetState"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [shouldLayout]("GI.Gtk.Objects.Widget#g:method:shouldLayout"), [show]("GI.Gtk.Objects.Widget#g:method:show"), [sizeAllocate]("GI.Gtk.Objects.Widget#g:method:sizeAllocate"), [snapshotChild]("GI.Gtk.Objects.Widget#g:method:snapshotChild"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [toggled]("GI.Gtk.Objects.ToggleButton#g:method:toggled"), [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"), [unsetStateFlags]("GI.Gtk.Objects.Widget#g:method:unsetStateFlags"), [updateProperty]("GI.Gtk.Interfaces.Accessible#g:method:updateProperty"), [updateRelation]("GI.Gtk.Interfaces.Accessible#g:method:updateRelation"), [updateState]("GI.Gtk.Interfaces.Accessible#g:method:updateState"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessibleRole]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleRole"), [getActionName]("GI.Gtk.Interfaces.Actionable#g:method:getActionName"), [getActionTargetValue]("GI.Gtk.Interfaces.Actionable#g:method:getActionTargetValue"), [getActive]("GI.Gtk.Objects.ToggleButton#g:method:getActive"), [getAllocatedBaseline]("GI.Gtk.Objects.Widget#g:method:getAllocatedBaseline"), [getAllocatedHeight]("GI.Gtk.Objects.Widget#g:method:getAllocatedHeight"), [getAllocatedWidth]("GI.Gtk.Objects.Widget#g:method:getAllocatedWidth"), [getAllocation]("GI.Gtk.Objects.Widget#g:method:getAllocation"), [getAncestor]("GI.Gtk.Objects.Widget#g:method:getAncestor"), [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getCanTarget]("GI.Gtk.Objects.Widget#g:method:getCanTarget"), [getChild]("GI.Gtk.Objects.Button#g:method:getChild"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getCssClasses]("GI.Gtk.Objects.Widget#g:method:getCssClasses"), [getCssName]("GI.Gtk.Objects.Widget#g:method:getCssName"), [getCursor]("GI.Gtk.Objects.Widget#g:method:getCursor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getFirstChild]("GI.Gtk.Objects.Widget#g:method:getFirstChild"), [getFocusChild]("GI.Gtk.Objects.Widget#g:method:getFocusChild"), [getFocusOnClick]("GI.Gtk.Objects.Widget#g:method:getFocusOnClick"), [getFocusable]("GI.Gtk.Objects.Widget#g:method:getFocusable"), [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"), [getHasFrame]("GI.Gtk.Objects.Button#g:method:getHasFrame"), [getHasTooltip]("GI.Gtk.Objects.Widget#g:method:getHasTooltip"), [getHeight]("GI.Gtk.Objects.Widget#g:method:getHeight"), [getHexpand]("GI.Gtk.Objects.Widget#g:method:getHexpand"), [getHexpandSet]("GI.Gtk.Objects.Widget#g:method:getHexpandSet"), [getIconName]("GI.Gtk.Objects.Button#g:method:getIconName"), [getLabel]("GI.Gtk.Objects.Button#g:method:getLabel"), [getLastChild]("GI.Gtk.Objects.Widget#g:method:getLastChild"), [getLayoutManager]("GI.Gtk.Objects.Widget#g:method:getLayoutManager"), [getMapped]("GI.Gtk.Objects.Widget#g:method:getMapped"), [getMarginBottom]("GI.Gtk.Objects.Widget#g:method:getMarginBottom"), [getMarginEnd]("GI.Gtk.Objects.Widget#g:method:getMarginEnd"), [getMarginStart]("GI.Gtk.Objects.Widget#g:method:getMarginStart"), [getMarginTop]("GI.Gtk.Objects.Widget#g:method:getMarginTop"), [getName]("GI.Gtk.Objects.Widget#g:method:getName"), [getNative]("GI.Gtk.Objects.Widget#g:method:getNative"), [getNextSibling]("GI.Gtk.Objects.Widget#g:method:getNextSibling"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getOverflow]("GI.Gtk.Objects.Widget#g:method:getOverflow"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPrevSibling]("GI.Gtk.Objects.Widget#g:method:getPrevSibling"), [getPrimaryClipboard]("GI.Gtk.Objects.Widget#g:method:getPrimaryClipboard"), [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"), [getRoot]("GI.Gtk.Objects.Widget#g:method:getRoot"), [getScaleFactor]("GI.Gtk.Objects.Widget#g:method:getScaleFactor"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getSize]("GI.Gtk.Objects.Widget#g:method:getSize"), [getSizeRequest]("GI.Gtk.Objects.Widget#g:method:getSizeRequest"), [getStateFlags]("GI.Gtk.Objects.Widget#g:method:getStateFlags"), [getStyleContext]("GI.Gtk.Objects.Widget#g:method:getStyleContext"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [getUseUnderline]("GI.Gtk.Objects.Button#g:method:getUseUnderline"), [getValign]("GI.Gtk.Objects.Widget#g:method:getValign"), [getVexpand]("GI.Gtk.Objects.Widget#g:method:getVexpand"), [getVexpandSet]("GI.Gtk.Objects.Widget#g:method:getVexpandSet"), [getVisible]("GI.Gtk.Objects.Widget#g:method:getVisible"), [getWidth]("GI.Gtk.Objects.Widget#g:method:getWidth").
-- 
-- ==== Setters
-- [setActionName]("GI.Gtk.Interfaces.Actionable#g:method:setActionName"), [setActionTargetValue]("GI.Gtk.Interfaces.Actionable#g:method:setActionTargetValue"), [setActive]("GI.Gtk.Objects.ToggleButton#g:method:setActive"), [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setChild]("GI.Gtk.Objects.Button#g:method:setChild"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setCssClasses]("GI.Gtk.Objects.Widget#g:method:setCssClasses"), [setCursor]("GI.Gtk.Objects.Widget#g:method:setCursor"), [setCursorFromName]("GI.Gtk.Objects.Widget#g:method:setCursorFromName"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDetailedActionName]("GI.Gtk.Interfaces.Actionable#g:method:setDetailedActionName"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setFocusChild]("GI.Gtk.Objects.Widget#g:method:setFocusChild"), [setFocusOnClick]("GI.Gtk.Objects.Widget#g:method:setFocusOnClick"), [setFocusable]("GI.Gtk.Objects.Widget#g:method:setFocusable"), [setFontMap]("GI.Gtk.Objects.Widget#g:method:setFontMap"), [setFontOptions]("GI.Gtk.Objects.Widget#g:method:setFontOptions"), [setGroup]("GI.Gtk.Objects.ToggleButton#g:method:setGroup"), [setHalign]("GI.Gtk.Objects.Widget#g:method:setHalign"), [setHasFrame]("GI.Gtk.Objects.Button#g:method:setHasFrame"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setIconName]("GI.Gtk.Objects.Button#g:method:setIconName"), [setLabel]("GI.Gtk.Objects.Button#g:method:setLabel"), [setLayoutManager]("GI.Gtk.Objects.Widget#g:method:setLayoutManager"), [setMarginBottom]("GI.Gtk.Objects.Widget#g:method:setMarginBottom"), [setMarginEnd]("GI.Gtk.Objects.Widget#g:method:setMarginEnd"), [setMarginStart]("GI.Gtk.Objects.Widget#g:method:setMarginStart"), [setMarginTop]("GI.Gtk.Objects.Widget#g:method:setMarginTop"), [setName]("GI.Gtk.Objects.Widget#g:method:setName"), [setOpacity]("GI.Gtk.Objects.Widget#g:method:setOpacity"), [setOverflow]("GI.Gtk.Objects.Widget#g:method:setOverflow"), [setParent]("GI.Gtk.Objects.Widget#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [setUseUnderline]("GI.Gtk.Objects.Button#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").

#if defined(ENABLE_OVERLOADING)
    ResolveToggleButtonMethod               ,
#endif

-- ** getActive #method:getActive#

#if defined(ENABLE_OVERLOADING)
    ToggleButtonGetActiveMethodInfo         ,
#endif
    toggleButtonGetActive                   ,


-- ** new #method:new#

    toggleButtonNew                         ,


-- ** newWithLabel #method:newWithLabel#

    toggleButtonNewWithLabel                ,


-- ** newWithMnemonic #method:newWithMnemonic#

    toggleButtonNewWithMnemonic             ,


-- ** setActive #method:setActive#

#if defined(ENABLE_OVERLOADING)
    ToggleButtonSetActiveMethodInfo         ,
#endif
    toggleButtonSetActive                   ,


-- ** setGroup #method:setGroup#

#if defined(ENABLE_OVERLOADING)
    ToggleButtonSetGroupMethodInfo          ,
#endif
    toggleButtonSetGroup                    ,


-- ** toggled #method:toggled#

#if defined(ENABLE_OVERLOADING)
    ToggleButtonToggledMethodInfo           ,
#endif
    toggleButtonToggled                     ,




 -- * Properties


-- ** active #attr:active#
-- | If the toggle button should be pressed in.

#if defined(ENABLE_OVERLOADING)
    ToggleButtonActivePropertyInfo          ,
#endif
    constructToggleButtonActive             ,
    getToggleButtonActive                   ,
    setToggleButtonActive                   ,
#if defined(ENABLE_OVERLOADING)
    toggleButtonActive                      ,
#endif


-- ** group #attr:group#
-- | The toggle button whose group this widget belongs to.

#if defined(ENABLE_OVERLOADING)
    ToggleButtonGroupPropertyInfo           ,
#endif
    clearToggleButtonGroup                  ,
    constructToggleButtonGroup              ,
    setToggleButtonGroup                    ,
#if defined(ENABLE_OVERLOADING)
    toggleButtonGroup                       ,
#endif




 -- * Signals


-- ** toggled #signal:toggled#

    ToggleButtonToggledCallback             ,
#if defined(ENABLE_OVERLOADING)
    ToggleButtonToggledSignalInfo           ,
#endif
    afterToggleButtonToggled                ,
    onToggleButtonToggled                   ,




    ) where

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

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

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Actionable as Gtk.Actionable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Objects.Button as Gtk.Button
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "gtk_toggle_button_get_type"
    c_gtk_toggle_button_get_type :: IO B.Types.GType

instance B.Types.TypedObject ToggleButton where
    glibType :: IO GType
glibType = IO GType
c_gtk_toggle_button_get_type

instance B.Types.GObject ToggleButton

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

instance O.HasParentTypes ToggleButton
type instance O.ParentTypes ToggleButton = '[Gtk.Button.Button, Gtk.Widget.Widget, GObject.Object.Object, Gtk.Accessible.Accessible, Gtk.Actionable.Actionable, Gtk.Buildable.Buildable, Gtk.ConstraintTarget.ConstraintTarget]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveToggleButtonMethod (t :: Symbol) (o :: *) :: * where
    ResolveToggleButtonMethod "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveToggleButtonMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveToggleButtonMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveToggleButtonMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveToggleButtonMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveToggleButtonMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    ResolveToggleButtonMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveToggleButtonMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveToggleButtonMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveToggleButtonMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveToggleButtonMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveToggleButtonMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveToggleButtonMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveToggleButtonMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveToggleButtonMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveToggleButtonMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveToggleButtonMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveToggleButtonMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveToggleButtonMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveToggleButtonMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveToggleButtonMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveToggleButtonMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveToggleButtonMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveToggleButtonMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveToggleButtonMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveToggleButtonMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveToggleButtonMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveToggleButtonMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveToggleButtonMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveToggleButtonMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveToggleButtonMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveToggleButtonMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveToggleButtonMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveToggleButtonMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveToggleButtonMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveToggleButtonMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveToggleButtonMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveToggleButtonMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveToggleButtonMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveToggleButtonMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveToggleButtonMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveToggleButtonMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveToggleButtonMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveToggleButtonMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveToggleButtonMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveToggleButtonMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveToggleButtonMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveToggleButtonMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveToggleButtonMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveToggleButtonMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveToggleButtonMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveToggleButtonMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveToggleButtonMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveToggleButtonMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveToggleButtonMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveToggleButtonMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveToggleButtonMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveToggleButtonMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveToggleButtonMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveToggleButtonMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveToggleButtonMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveToggleButtonMethod "resetProperty" o = Gtk.Accessible.AccessibleResetPropertyMethodInfo
    ResolveToggleButtonMethod "resetRelation" o = Gtk.Accessible.AccessibleResetRelationMethodInfo
    ResolveToggleButtonMethod "resetState" o = Gtk.Accessible.AccessibleResetStateMethodInfo
    ResolveToggleButtonMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveToggleButtonMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    ResolveToggleButtonMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveToggleButtonMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveToggleButtonMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveToggleButtonMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveToggleButtonMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveToggleButtonMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveToggleButtonMethod "toggled" o = ToggleButtonToggledMethodInfo
    ResolveToggleButtonMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveToggleButtonMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveToggleButtonMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveToggleButtonMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveToggleButtonMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveToggleButtonMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveToggleButtonMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveToggleButtonMethod "updateProperty" o = Gtk.Accessible.AccessibleUpdatePropertyMethodInfo
    ResolveToggleButtonMethod "updateRelation" o = Gtk.Accessible.AccessibleUpdateRelationMethodInfo
    ResolveToggleButtonMethod "updateState" o = Gtk.Accessible.AccessibleUpdateStateMethodInfo
    ResolveToggleButtonMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveToggleButtonMethod "getAccessibleRole" o = Gtk.Accessible.AccessibleGetAccessibleRoleMethodInfo
    ResolveToggleButtonMethod "getActionName" o = Gtk.Actionable.ActionableGetActionNameMethodInfo
    ResolveToggleButtonMethod "getActionTargetValue" o = Gtk.Actionable.ActionableGetActionTargetValueMethodInfo
    ResolveToggleButtonMethod "getActive" o = ToggleButtonGetActiveMethodInfo
    ResolveToggleButtonMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveToggleButtonMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveToggleButtonMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveToggleButtonMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveToggleButtonMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveToggleButtonMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveToggleButtonMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveToggleButtonMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveToggleButtonMethod "getChild" o = Gtk.Button.ButtonGetChildMethodInfo
    ResolveToggleButtonMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveToggleButtonMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveToggleButtonMethod "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveToggleButtonMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    ResolveToggleButtonMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveToggleButtonMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveToggleButtonMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveToggleButtonMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveToggleButtonMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveToggleButtonMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveToggleButtonMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveToggleButtonMethod "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    ResolveToggleButtonMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveToggleButtonMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveToggleButtonMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveToggleButtonMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveToggleButtonMethod "getHasFrame" o = Gtk.Button.ButtonGetHasFrameMethodInfo
    ResolveToggleButtonMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveToggleButtonMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveToggleButtonMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveToggleButtonMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveToggleButtonMethod "getIconName" o = Gtk.Button.ButtonGetIconNameMethodInfo
    ResolveToggleButtonMethod "getLabel" o = Gtk.Button.ButtonGetLabelMethodInfo
    ResolveToggleButtonMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveToggleButtonMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveToggleButtonMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveToggleButtonMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveToggleButtonMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveToggleButtonMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveToggleButtonMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveToggleButtonMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveToggleButtonMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    ResolveToggleButtonMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveToggleButtonMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveToggleButtonMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveToggleButtonMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveToggleButtonMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveToggleButtonMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveToggleButtonMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveToggleButtonMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveToggleButtonMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveToggleButtonMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveToggleButtonMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveToggleButtonMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveToggleButtonMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveToggleButtonMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveToggleButtonMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveToggleButtonMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveToggleButtonMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveToggleButtonMethod "getSize" o = Gtk.Widget.WidgetGetSizeMethodInfo
    ResolveToggleButtonMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveToggleButtonMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveToggleButtonMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveToggleButtonMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveToggleButtonMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveToggleButtonMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveToggleButtonMethod "getUseUnderline" o = Gtk.Button.ButtonGetUseUnderlineMethodInfo
    ResolveToggleButtonMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveToggleButtonMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveToggleButtonMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveToggleButtonMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveToggleButtonMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveToggleButtonMethod "setActionName" o = Gtk.Actionable.ActionableSetActionNameMethodInfo
    ResolveToggleButtonMethod "setActionTargetValue" o = Gtk.Actionable.ActionableSetActionTargetValueMethodInfo
    ResolveToggleButtonMethod "setActive" o = ToggleButtonSetActiveMethodInfo
    ResolveToggleButtonMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveToggleButtonMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveToggleButtonMethod "setChild" o = Gtk.Button.ButtonSetChildMethodInfo
    ResolveToggleButtonMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveToggleButtonMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    ResolveToggleButtonMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveToggleButtonMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveToggleButtonMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveToggleButtonMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveToggleButtonMethod "setDetailedActionName" o = Gtk.Actionable.ActionableSetDetailedActionNameMethodInfo
    ResolveToggleButtonMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveToggleButtonMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveToggleButtonMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveToggleButtonMethod "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    ResolveToggleButtonMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveToggleButtonMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveToggleButtonMethod "setGroup" o = ToggleButtonSetGroupMethodInfo
    ResolveToggleButtonMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveToggleButtonMethod "setHasFrame" o = Gtk.Button.ButtonSetHasFrameMethodInfo
    ResolveToggleButtonMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveToggleButtonMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveToggleButtonMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveToggleButtonMethod "setIconName" o = Gtk.Button.ButtonSetIconNameMethodInfo
    ResolveToggleButtonMethod "setLabel" o = Gtk.Button.ButtonSetLabelMethodInfo
    ResolveToggleButtonMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveToggleButtonMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveToggleButtonMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveToggleButtonMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveToggleButtonMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveToggleButtonMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveToggleButtonMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveToggleButtonMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveToggleButtonMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveToggleButtonMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveToggleButtonMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveToggleButtonMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveToggleButtonMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveToggleButtonMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveToggleButtonMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveToggleButtonMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveToggleButtonMethod "setUseUnderline" o = Gtk.Button.ButtonSetUseUnderlineMethodInfo
    ResolveToggleButtonMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveToggleButtonMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveToggleButtonMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveToggleButtonMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveToggleButtonMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- signal ToggleButton::toggled
-- | Emitted whenever the @GtkToggleButton@\'s state is changed.
type ToggleButtonToggledCallback =
    IO ()

type C_ToggleButtonToggledCallback =
    Ptr ToggleButton ->                     -- object
    Ptr () ->                               -- user_data
    IO ()

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

wrap_ToggleButtonToggledCallback :: 
    GObject a => (a -> ToggleButtonToggledCallback) ->
    C_ToggleButtonToggledCallback
wrap_ToggleButtonToggledCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_ToggleButtonToggledCallback
wrap_ToggleButtonToggledCallback a -> IO ()
gi'cb Ptr ToggleButton
gi'selfPtr Ptr ()
_ = do
    Ptr ToggleButton -> (ToggleButton -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr ToggleButton
gi'selfPtr ((ToggleButton -> IO ()) -> IO ())
-> (ToggleButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ToggleButton
gi'self -> a -> IO ()
gi'cb (ToggleButton -> a
Coerce.coerce ToggleButton
gi'self) 


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

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


#if defined(ENABLE_OVERLOADING)
data ToggleButtonToggledSignalInfo
instance SignalInfo ToggleButtonToggledSignalInfo where
    type HaskellCallbackType ToggleButtonToggledSignalInfo = ToggleButtonToggledCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ToggleButtonToggledCallback cb
        cb'' <- mk_ToggleButtonToggledCallback cb'
        connectSignalFunPtr obj "toggled" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ToggleButton::toggled"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ToggleButton.html#g:signal:toggled"})

#endif

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

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

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

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

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

-- VVV Prop "group"
   -- Type: TInterface (Name {namespace = "Gtk", name = "ToggleButton"})
   -- Flags: [PropertyWritable]
   -- Nullable: (Nothing,Just True)

-- | Set the value of the “@group@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' toggleButton [ #group 'Data.GI.Base.Attributes.:=' value ]
-- @
setToggleButtonGroup :: (MonadIO m, IsToggleButton o, IsToggleButton a) => o -> a -> m ()
setToggleButtonGroup :: forall (m :: * -> *) o a.
(MonadIO m, IsToggleButton o, IsToggleButton a) =>
o -> a -> m ()
setToggleButtonGroup o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"group" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@group@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructToggleButtonGroup :: (IsToggleButton o, MIO.MonadIO m, IsToggleButton a) => a -> m (GValueConstruct o)
constructToggleButtonGroup :: forall o (m :: * -> *) a.
(IsToggleButton o, MonadIO m, IsToggleButton a) =>
a -> m (GValueConstruct o)
constructToggleButtonGroup a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"group" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@group@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #group
-- @
clearToggleButtonGroup :: (MonadIO m, IsToggleButton o) => o -> m ()
clearToggleButtonGroup :: forall (m :: * -> *) o. (MonadIO m, IsToggleButton o) => o -> m ()
clearToggleButtonGroup o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe ToggleButton -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"group" (Maybe ToggleButton
forall a. Maybe a
Nothing :: Maybe ToggleButton)

#if defined(ENABLE_OVERLOADING)
data ToggleButtonGroupPropertyInfo
instance AttrInfo ToggleButtonGroupPropertyInfo where
    type AttrAllowedOps ToggleButtonGroupPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrClear]
    type AttrBaseTypeConstraint ToggleButtonGroupPropertyInfo = IsToggleButton
    type AttrSetTypeConstraint ToggleButtonGroupPropertyInfo = IsToggleButton
    type AttrTransferTypeConstraint ToggleButtonGroupPropertyInfo = IsToggleButton
    type AttrTransferType ToggleButtonGroupPropertyInfo = ToggleButton
    type AttrGetType ToggleButtonGroupPropertyInfo = ()
    type AttrLabel ToggleButtonGroupPropertyInfo = "group"
    type AttrOrigin ToggleButtonGroupPropertyInfo = ToggleButton
    attrGet = undefined
    attrSet = setToggleButtonGroup
    attrTransfer _ v = do
        unsafeCastTo ToggleButton v
    attrConstruct = constructToggleButtonGroup
    attrClear = clearToggleButtonGroup
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ToggleButton.group"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ToggleButton.html#g:attr:group"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ToggleButton
type instance O.AttributeList ToggleButton = ToggleButtonAttributeList
type ToggleButtonAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("actionName", Gtk.Actionable.ActionableActionNamePropertyInfo), '("actionTarget", Gtk.Actionable.ActionableActionTargetPropertyInfo), '("active", ToggleButtonActivePropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("child", Gtk.Button.ButtonChildPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("group", ToggleButtonGroupPropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasFrame", Gtk.Button.ButtonHasFramePropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("iconName", Gtk.Button.ButtonIconNamePropertyInfo), '("label", Gtk.Button.ButtonLabelPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("useUnderline", Gtk.Button.ButtonUseUnderlinePropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
toggleButtonActive :: AttrLabelProxy "active"
toggleButtonActive = AttrLabelProxy

toggleButtonGroup :: AttrLabelProxy "group"
toggleButtonGroup = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ToggleButton = ToggleButtonSignalList
type ToggleButtonSignalList = ('[ '("activate", Gtk.Button.ButtonActivateSignalInfo), '("clicked", Gtk.Button.ButtonClickedSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("toggled", ToggleButtonToggledSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "gtk_toggle_button_new" gtk_toggle_button_new :: 
    IO (Ptr ToggleButton)

-- | Creates a new toggle button.
-- 
-- A widget should be packed into the button, as in 'GI.Gtk.Objects.Button.buttonNew'.
toggleButtonNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m ToggleButton
    -- ^ __Returns:__ a new toggle button.
toggleButtonNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m ToggleButton
toggleButtonNew  = IO ToggleButton -> m ToggleButton
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ToggleButton -> m ToggleButton)
-> IO ToggleButton -> m ToggleButton
forall a b. (a -> b) -> a -> b
$ do
    Ptr ToggleButton
result <- IO (Ptr ToggleButton)
gtk_toggle_button_new
    Text -> Ptr ToggleButton -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"toggleButtonNew" Ptr ToggleButton
result
    ToggleButton
result' <- ((ManagedPtr ToggleButton -> ToggleButton)
-> Ptr ToggleButton -> IO ToggleButton
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ToggleButton -> ToggleButton
ToggleButton) Ptr ToggleButton
result
    ToggleButton -> IO ToggleButton
forall (m :: * -> *) a. Monad m => a -> m a
return ToggleButton
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method ToggleButton::new_with_label
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a string containing the message to be placed in the toggle button."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "ToggleButton" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_toggle_button_new_with_label" gtk_toggle_button_new_with_label :: 
    CString ->                              -- label : TBasicType TUTF8
    IO (Ptr ToggleButton)

-- | Creates a new toggle button with a text label.
toggleButtonNewWithLabel ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@label@/: a string containing the message to be placed in the toggle button.
    -> m ToggleButton
    -- ^ __Returns:__ a new toggle button.
toggleButtonNewWithLabel :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m ToggleButton
toggleButtonNewWithLabel Text
label = IO ToggleButton -> m ToggleButton
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ToggleButton -> m ToggleButton)
-> IO ToggleButton -> m ToggleButton
forall a b. (a -> b) -> a -> b
$ do
    CString
label' <- Text -> IO CString
textToCString Text
label
    Ptr ToggleButton
result <- CString -> IO (Ptr ToggleButton)
gtk_toggle_button_new_with_label CString
label'
    Text -> Ptr ToggleButton -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"toggleButtonNewWithLabel" Ptr ToggleButton
result
    ToggleButton
result' <- ((ManagedPtr ToggleButton -> ToggleButton)
-> Ptr ToggleButton -> IO ToggleButton
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ToggleButton -> ToggleButton
ToggleButton) Ptr ToggleButton
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
label'
    ToggleButton -> IO ToggleButton
forall (m :: * -> *) a. Monad m => a -> m a
return ToggleButton
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method ToggleButton::new_with_mnemonic
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the text of the button, with an underscore in front of the\n  mnemonic character"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "ToggleButton" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_toggle_button_new_with_mnemonic" gtk_toggle_button_new_with_mnemonic :: 
    CString ->                              -- label : TBasicType TUTF8
    IO (Ptr ToggleButton)

-- | Creates a new @GtkToggleButton@ containing a label.
-- 
-- The label will be created using 'GI.Gtk.Objects.Label.labelNewWithMnemonic',
-- so underscores in /@label@/ indicate the mnemonic for the button.
toggleButtonNewWithMnemonic ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@label@/: the text of the button, with an underscore in front of the
    --   mnemonic character
    -> m ToggleButton
    -- ^ __Returns:__ a new @GtkToggleButton@
toggleButtonNewWithMnemonic :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m ToggleButton
toggleButtonNewWithMnemonic Text
label = IO ToggleButton -> m ToggleButton
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ToggleButton -> m ToggleButton)
-> IO ToggleButton -> m ToggleButton
forall a b. (a -> b) -> a -> b
$ do
    CString
label' <- Text -> IO CString
textToCString Text
label
    Ptr ToggleButton
result <- CString -> IO (Ptr ToggleButton)
gtk_toggle_button_new_with_mnemonic CString
label'
    Text -> Ptr ToggleButton -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"toggleButtonNewWithMnemonic" Ptr ToggleButton
result
    ToggleButton
result' <- ((ManagedPtr ToggleButton -> ToggleButton)
-> Ptr ToggleButton -> IO ToggleButton
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ToggleButton -> ToggleButton
ToggleButton) Ptr ToggleButton
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
label'
    ToggleButton -> IO ToggleButton
forall (m :: * -> *) a. Monad m => a -> m a
return ToggleButton
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "gtk_toggle_button_get_active" gtk_toggle_button_get_active :: 
    Ptr ToggleButton ->                     -- toggle_button : TInterface (Name {namespace = "Gtk", name = "ToggleButton"})
    IO CInt

-- | Queries a @GtkToggleButton@ and returns its current state.
-- 
-- Returns 'P.True' if the toggle button is pressed in and 'P.False'
-- if it is raised.
toggleButtonGetActive ::
    (B.CallStack.HasCallStack, MonadIO m, IsToggleButton a) =>
    a
    -- ^ /@toggleButton@/: a @GtkToggleButton@.
    -> m Bool
    -- ^ __Returns:__ whether the button is pressed
toggleButtonGetActive :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsToggleButton a) =>
a -> m Bool
toggleButtonGetActive a
toggleButton = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr ToggleButton
toggleButton' <- a -> IO (Ptr ToggleButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
toggleButton
    CInt
result <- Ptr ToggleButton -> IO CInt
gtk_toggle_button_get_active Ptr ToggleButton
toggleButton'
    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
toggleButton
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ToggleButtonGetActiveMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsToggleButton a) => O.OverloadedMethod ToggleButtonGetActiveMethodInfo a signature where
    overloadedMethod = toggleButtonGetActive

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


#endif

-- method ToggleButton::set_active
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "toggle_button"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ToggleButton" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkToggleButton`."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "is_active"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE or %FALSE." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_toggle_button_set_active" gtk_toggle_button_set_active :: 
    Ptr ToggleButton ->                     -- toggle_button : TInterface (Name {namespace = "Gtk", name = "ToggleButton"})
    CInt ->                                 -- is_active : TBasicType TBoolean
    IO ()

-- | Sets the status of the toggle button.
-- 
-- Set to 'P.True' if you want the @GtkToggleButton@ to be “pressed in”,
-- and 'P.False' to raise it.
-- 
-- If the status of the button changes, this action causes the
-- [signal/@gtkToggleButton@/[toggled](#g:signal:toggled)] signal to be emitted.
toggleButtonSetActive ::
    (B.CallStack.HasCallStack, MonadIO m, IsToggleButton a) =>
    a
    -- ^ /@toggleButton@/: a @GtkToggleButton@.
    -> Bool
    -- ^ /@isActive@/: 'P.True' or 'P.False'.
    -> m ()
toggleButtonSetActive :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsToggleButton a) =>
a -> Bool -> m ()
toggleButtonSetActive a
toggleButton Bool
isActive = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ToggleButton
toggleButton' <- a -> IO (Ptr ToggleButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
toggleButton
    let isActive' :: CInt
isActive' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
isActive
    Ptr ToggleButton -> CInt -> IO ()
gtk_toggle_button_set_active Ptr ToggleButton
toggleButton' CInt
isActive'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
toggleButton
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ToggleButtonSetActiveMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsToggleButton a) => O.OverloadedMethod ToggleButtonSetActiveMethodInfo a signature where
    overloadedMethod = toggleButtonSetActive

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


#endif

-- method ToggleButton::set_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "toggle_button"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ToggleButton" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkToggleButton`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ToggleButton" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "another `GtkToggleButton` to\n  form a group with"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_toggle_button_set_group" gtk_toggle_button_set_group :: 
    Ptr ToggleButton ->                     -- toggle_button : TInterface (Name {namespace = "Gtk", name = "ToggleButton"})
    Ptr ToggleButton ->                     -- group : TInterface (Name {namespace = "Gtk", name = "ToggleButton"})
    IO ()

-- | Adds /@self@/ to the group of /@group@/.
-- 
-- In a group of multiple toggle buttons, only one button can be active
-- at a time.
-- 
-- Setting up groups in a cycle leads to undefined behavior.
-- 
-- Note that the same effect can be achieved via the t'GI.Gtk.Interfaces.Actionable.Actionable'
-- API, by using the same action with parameter type and state type \'s\'
-- for all buttons in the group, and giving each button its own target
-- value.
toggleButtonSetGroup ::
    (B.CallStack.HasCallStack, MonadIO m, IsToggleButton a, IsToggleButton b) =>
    a
    -- ^ /@toggleButton@/: a @GtkToggleButton@
    -> Maybe (b)
    -- ^ /@group@/: another @GtkToggleButton@ to
    --   form a group with
    -> m ()
toggleButtonSetGroup :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsToggleButton a, IsToggleButton b) =>
a -> Maybe b -> m ()
toggleButtonSetGroup a
toggleButton Maybe b
group = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ToggleButton
toggleButton' <- a -> IO (Ptr ToggleButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
toggleButton
    Ptr ToggleButton
maybeGroup <- case Maybe b
group of
        Maybe b
Nothing -> Ptr ToggleButton -> IO (Ptr ToggleButton)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ToggleButton
forall a. Ptr a
nullPtr
        Just b
jGroup -> do
            Ptr ToggleButton
jGroup' <- b -> IO (Ptr ToggleButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jGroup
            Ptr ToggleButton -> IO (Ptr ToggleButton)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ToggleButton
jGroup'
    Ptr ToggleButton -> Ptr ToggleButton -> IO ()
gtk_toggle_button_set_group Ptr ToggleButton
toggleButton' Ptr ToggleButton
maybeGroup
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
toggleButton
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
group b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ToggleButtonSetGroupMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsToggleButton a, IsToggleButton b) => O.OverloadedMethod ToggleButtonSetGroupMethodInfo a signature where
    overloadedMethod = toggleButtonSetGroup

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


#endif

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

foreign import ccall "gtk_toggle_button_toggled" gtk_toggle_button_toggled :: 
    Ptr ToggleButton ->                     -- toggle_button : TInterface (Name {namespace = "Gtk", name = "ToggleButton"})
    IO ()

-- | Emits the [toggled](#g:signal:toggled) signal on the @GtkToggleButton@.
-- 
-- There is no good reason for an application ever to call this function.
toggleButtonToggled ::
    (B.CallStack.HasCallStack, MonadIO m, IsToggleButton a) =>
    a
    -- ^ /@toggleButton@/: a @GtkToggleButton@.
    -> m ()
toggleButtonToggled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsToggleButton a) =>
a -> m ()
toggleButtonToggled a
toggleButton = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ToggleButton
toggleButton' <- a -> IO (Ptr ToggleButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
toggleButton
    Ptr ToggleButton -> IO ()
gtk_toggle_button_toggled Ptr ToggleButton
toggleButton'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
toggleButton
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ToggleButtonToggledMethodInfo
instance (signature ~ (m ()), MonadIO m, IsToggleButton a) => O.OverloadedMethod ToggleButtonToggledMethodInfo a signature where
    overloadedMethod = toggleButtonToggled

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


#endif