{-# LANGUAGE ImplicitParams, RankNTypes, 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.RadioAction.RadioAction' is similar to t'GI.Gtk.Objects.RadioMenuItem.RadioMenuItem'. A number of radio
-- actions can be linked together so that only one may be active at any
-- one time.

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

module GI.Gtk.Objects.RadioAction
    ( 

-- * Exported types
    RadioAction(..)                         ,
    IsRadioAction                           ,
    toRadioAction                           ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [activate]("GI.Gtk.Objects.Action#g:method:activate"), [addChild]("GI.Gtk.Interfaces.Buildable#g:method:addChild"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [blockActivate]("GI.Gtk.Objects.Action#g:method:blockActivate"), [connectAccelerator]("GI.Gtk.Objects.Action#g:method:connectAccelerator"), [constructChild]("GI.Gtk.Interfaces.Buildable#g:method:constructChild"), [createIcon]("GI.Gtk.Objects.Action#g:method:createIcon"), [createMenu]("GI.Gtk.Objects.Action#g:method:createMenu"), [createMenuItem]("GI.Gtk.Objects.Action#g:method:createMenuItem"), [createToolItem]("GI.Gtk.Objects.Action#g:method:createToolItem"), [customFinished]("GI.Gtk.Interfaces.Buildable#g:method:customFinished"), [customTagEnd]("GI.Gtk.Interfaces.Buildable#g:method:customTagEnd"), [customTagStart]("GI.Gtk.Interfaces.Buildable#g:method:customTagStart"), [disconnectAccelerator]("GI.Gtk.Objects.Action#g:method:disconnectAccelerator"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isSensitive]("GI.Gtk.Objects.Action#g:method:isSensitive"), [isVisible]("GI.Gtk.Objects.Action#g:method:isVisible"), [joinGroup]("GI.Gtk.Objects.RadioAction#g:method:joinGroup"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [parserFinished]("GI.Gtk.Interfaces.Buildable#g:method:parserFinished"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [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.ToggleAction#g:method:toggled"), [unblockActivate]("GI.Gtk.Objects.Action#g:method:unblockActivate"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccelClosure]("GI.Gtk.Objects.Action#g:method:getAccelClosure"), [getAccelPath]("GI.Gtk.Objects.Action#g:method:getAccelPath"), [getActive]("GI.Gtk.Objects.ToggleAction#g:method:getActive"), [getAlwaysShowImage]("GI.Gtk.Objects.Action#g:method:getAlwaysShowImage"), [getCurrentValue]("GI.Gtk.Objects.RadioAction#g:method:getCurrentValue"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDrawAsRadio]("GI.Gtk.Objects.ToggleAction#g:method:getDrawAsRadio"), [getGicon]("GI.Gtk.Objects.Action#g:method:getGicon"), [getGroup]("GI.Gtk.Objects.RadioAction#g:method:getGroup"), [getIconName]("GI.Gtk.Objects.Action#g:method:getIconName"), [getInternalChild]("GI.Gtk.Interfaces.Buildable#g:method:getInternalChild"), [getIsImportant]("GI.Gtk.Objects.Action#g:method:getIsImportant"), [getLabel]("GI.Gtk.Objects.Action#g:method:getLabel"), [getName]("GI.Gtk.Objects.Action#g:method:getName"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getProxies]("GI.Gtk.Objects.Action#g:method:getProxies"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSensitive]("GI.Gtk.Objects.Action#g:method:getSensitive"), [getShortLabel]("GI.Gtk.Objects.Action#g:method:getShortLabel"), [getStockId]("GI.Gtk.Objects.Action#g:method:getStockId"), [getTooltip]("GI.Gtk.Objects.Action#g:method:getTooltip"), [getVisible]("GI.Gtk.Objects.Action#g:method:getVisible"), [getVisibleHorizontal]("GI.Gtk.Objects.Action#g:method:getVisibleHorizontal"), [getVisibleVertical]("GI.Gtk.Objects.Action#g:method:getVisibleVertical").
-- 
-- ==== Setters
-- [setAccelGroup]("GI.Gtk.Objects.Action#g:method:setAccelGroup"), [setAccelPath]("GI.Gtk.Objects.Action#g:method:setAccelPath"), [setActive]("GI.Gtk.Objects.ToggleAction#g:method:setActive"), [setAlwaysShowImage]("GI.Gtk.Objects.Action#g:method:setAlwaysShowImage"), [setBuildableProperty]("GI.Gtk.Interfaces.Buildable#g:method:setBuildableProperty"), [setCurrentValue]("GI.Gtk.Objects.RadioAction#g:method:setCurrentValue"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDrawAsRadio]("GI.Gtk.Objects.ToggleAction#g:method:setDrawAsRadio"), [setGicon]("GI.Gtk.Objects.Action#g:method:setGicon"), [setGroup]("GI.Gtk.Objects.RadioAction#g:method:setGroup"), [setIconName]("GI.Gtk.Objects.Action#g:method:setIconName"), [setIsImportant]("GI.Gtk.Objects.Action#g:method:setIsImportant"), [setLabel]("GI.Gtk.Objects.Action#g:method:setLabel"), [setName]("GI.Gtk.Interfaces.Buildable#g:method:setName"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setSensitive]("GI.Gtk.Objects.Action#g:method:setSensitive"), [setShortLabel]("GI.Gtk.Objects.Action#g:method:setShortLabel"), [setStockId]("GI.Gtk.Objects.Action#g:method:setStockId"), [setTooltip]("GI.Gtk.Objects.Action#g:method:setTooltip"), [setVisible]("GI.Gtk.Objects.Action#g:method:setVisible"), [setVisibleHorizontal]("GI.Gtk.Objects.Action#g:method:setVisibleHorizontal"), [setVisibleVertical]("GI.Gtk.Objects.Action#g:method:setVisibleVertical").

#if defined(ENABLE_OVERLOADING)
    ResolveRadioActionMethod                ,
#endif

-- ** getCurrentValue #method:getCurrentValue#

#if defined(ENABLE_OVERLOADING)
    RadioActionGetCurrentValueMethodInfo    ,
#endif
    radioActionGetCurrentValue              ,


-- ** getGroup #method:getGroup#

#if defined(ENABLE_OVERLOADING)
    RadioActionGetGroupMethodInfo           ,
#endif
    radioActionGetGroup                     ,


-- ** joinGroup #method:joinGroup#

#if defined(ENABLE_OVERLOADING)
    RadioActionJoinGroupMethodInfo          ,
#endif
    radioActionJoinGroup                    ,


-- ** new #method:new#

    radioActionNew                          ,


-- ** setCurrentValue #method:setCurrentValue#

#if defined(ENABLE_OVERLOADING)
    RadioActionSetCurrentValueMethodInfo    ,
#endif
    radioActionSetCurrentValue              ,


-- ** setGroup #method:setGroup#

#if defined(ENABLE_OVERLOADING)
    RadioActionSetGroupMethodInfo           ,
#endif
    radioActionSetGroup                     ,




 -- * Properties


-- ** currentValue #attr:currentValue#
-- | The value property of the currently active member of the group to which
-- this action belongs.
-- 
-- /Since: 2.10/

#if defined(ENABLE_OVERLOADING)
    RadioActionCurrentValuePropertyInfo     ,
#endif
    constructRadioActionCurrentValue        ,
    getRadioActionCurrentValue              ,
#if defined(ENABLE_OVERLOADING)
    radioActionCurrentValue                 ,
#endif
    setRadioActionCurrentValue              ,


-- ** group #attr:group#
-- | Sets a new group for a radio action.
-- 
-- /Since: 2.4/

#if defined(ENABLE_OVERLOADING)
    RadioActionGroupPropertyInfo            ,
#endif
    clearRadioActionGroup                   ,
    constructRadioActionGroup               ,
#if defined(ENABLE_OVERLOADING)
    radioActionGroup                        ,
#endif
    setRadioActionGroup                     ,


-- ** value #attr:value#
-- | The value is an arbitrary integer which can be used as a
-- convenient way to determine which action in the group is
-- currently active in an [activate](#g:signal:activate) or [changed](#g:signal:changed) signal handler.
-- See 'GI.Gtk.Objects.RadioAction.radioActionGetCurrentValue' and t'GI.Gtk.Structs.RadioActionEntry.RadioActionEntry'
-- for convenient ways to get and set this property.
-- 
-- /Since: 2.4/

#if defined(ENABLE_OVERLOADING)
    RadioActionValuePropertyInfo            ,
#endif
    constructRadioActionValue               ,
    getRadioActionValue                     ,
#if defined(ENABLE_OVERLOADING)
    radioActionValue                        ,
#endif
    setRadioActionValue                     ,




 -- * Signals


-- ** changed #signal:changed#

    RadioActionChangedCallback              ,
#if defined(ENABLE_OVERLOADING)
    RadioActionChangedSignalInfo            ,
#endif
    afterRadioActionChanged                 ,
    onRadioActionChanged                    ,




    ) where

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

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

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.Atk.Objects.Object as Atk.Object
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.MarkupParser as GLib.MarkupParser
import qualified GI.GObject.Callbacks as GObject.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Enums as Gdk.Enums
import qualified GI.Gdk.Flags as Gdk.Flags
import qualified GI.Gdk.Objects.Device as Gdk.Device
import qualified GI.Gdk.Objects.Display as Gdk.Display
import qualified GI.Gdk.Objects.DragContext as Gdk.DragContext
import qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import qualified GI.Gdk.Objects.Screen as Gdk.Screen
import qualified GI.Gdk.Objects.Visual as Gdk.Visual
import qualified GI.Gdk.Objects.Window as Gdk.Window
import qualified GI.Gdk.Structs.Atom as Gdk.Atom
import qualified GI.Gdk.Structs.Color as Gdk.Color
import qualified GI.Gdk.Structs.EventAny as Gdk.EventAny
import qualified GI.Gdk.Structs.EventButton as Gdk.EventButton
import qualified GI.Gdk.Structs.EventConfigure as Gdk.EventConfigure
import qualified GI.Gdk.Structs.EventCrossing as Gdk.EventCrossing
import qualified GI.Gdk.Structs.EventExpose as Gdk.EventExpose
import qualified GI.Gdk.Structs.EventFocus as Gdk.EventFocus
import qualified GI.Gdk.Structs.EventGrabBroken as Gdk.EventGrabBroken
import qualified GI.Gdk.Structs.EventKey as Gdk.EventKey
import qualified GI.Gdk.Structs.EventMotion as Gdk.EventMotion
import qualified GI.Gdk.Structs.EventOwnerChange as Gdk.EventOwnerChange
import qualified GI.Gdk.Structs.EventProperty as Gdk.EventProperty
import qualified GI.Gdk.Structs.EventProximity as Gdk.EventProximity
import qualified GI.Gdk.Structs.EventScroll as Gdk.EventScroll
import qualified GI.Gdk.Structs.EventSelection as Gdk.EventSelection
import qualified GI.Gdk.Structs.EventVisibility as Gdk.EventVisibility
import qualified GI.Gdk.Structs.EventWindowState as Gdk.EventWindowState
import qualified GI.Gdk.Structs.Geometry as Gdk.Geometry
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import qualified GI.Gdk.Unions.Event as Gdk.Event
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Flags as Gio.Flags
import qualified GI.Gio.Interfaces.ActionGroup as Gio.ActionGroup
import qualified GI.Gio.Interfaces.ActionMap as Gio.ActionMap
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Objects.Application as Gio.Application
import qualified GI.Gio.Objects.Menu as Gio.Menu
import qualified GI.Gio.Objects.MenuModel as Gio.MenuModel
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.StyleProvider as Gtk.StyleProvider
import {-# SOURCE #-} qualified GI.Gtk.Objects.AccelGroup as Gtk.AccelGroup
import {-# SOURCE #-} qualified GI.Gtk.Objects.Action as Gtk.Action
import {-# SOURCE #-} qualified GI.Gtk.Objects.ActionGroup as Gtk.ActionGroup
import {-# SOURCE #-} qualified GI.Gtk.Objects.Adjustment as Gtk.Adjustment
import {-# SOURCE #-} qualified GI.Gtk.Objects.Application as Gtk.Application
import {-# SOURCE #-} qualified GI.Gtk.Objects.Bin as Gtk.Bin
import {-# SOURCE #-} qualified GI.Gtk.Objects.Builder as Gtk.Builder
import {-# SOURCE #-} qualified GI.Gtk.Objects.Clipboard as Gtk.Clipboard
import {-# SOURCE #-} qualified GI.Gtk.Objects.Container as Gtk.Container
import {-# SOURCE #-} qualified GI.Gtk.Objects.IconFactory as Gtk.IconFactory
import {-# SOURCE #-} qualified GI.Gtk.Objects.RcStyle as Gtk.RcStyle
import {-# SOURCE #-} qualified GI.Gtk.Objects.Settings as Gtk.Settings
import {-# SOURCE #-} qualified GI.Gtk.Objects.Style as Gtk.Style
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleContext as Gtk.StyleContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleProperties as Gtk.StyleProperties
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextBuffer as Gtk.TextBuffer
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextChildAnchor as Gtk.TextChildAnchor
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextMark as Gtk.TextMark
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextTag as Gtk.TextTag
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextTagTable as Gtk.TextTagTable
import {-# SOURCE #-} qualified GI.Gtk.Objects.ToggleAction as Gtk.ToggleAction
import {-# SOURCE #-} qualified GI.Gtk.Objects.Tooltip as Gtk.Tooltip
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Objects.Window as Gtk.Window
import {-# SOURCE #-} qualified GI.Gtk.Objects.WindowGroup as Gtk.WindowGroup
import {-# SOURCE #-} qualified GI.Gtk.Structs.AccelGroupEntry as Gtk.AccelGroupEntry
import {-# SOURCE #-} qualified GI.Gtk.Structs.AccelKey as Gtk.AccelKey
import {-# SOURCE #-} qualified GI.Gtk.Structs.Border as Gtk.Border
import {-# SOURCE #-} qualified GI.Gtk.Structs.CssSection as Gtk.CssSection
import {-# SOURCE #-} qualified GI.Gtk.Structs.IconSet as Gtk.IconSet
import {-# SOURCE #-} qualified GI.Gtk.Structs.IconSource as Gtk.IconSource
import {-# SOURCE #-} qualified GI.Gtk.Structs.Requisition as Gtk.Requisition
import {-# SOURCE #-} qualified GI.Gtk.Structs.SelectionData as Gtk.SelectionData
import {-# SOURCE #-} qualified GI.Gtk.Structs.SettingsValue as Gtk.SettingsValue
import {-# SOURCE #-} qualified GI.Gtk.Structs.SymbolicColor as Gtk.SymbolicColor
import {-# SOURCE #-} qualified GI.Gtk.Structs.TargetEntry as Gtk.TargetEntry
import {-# SOURCE #-} qualified GI.Gtk.Structs.TargetList as Gtk.TargetList
import {-# SOURCE #-} qualified GI.Gtk.Structs.TextAppearance as Gtk.TextAppearance
import {-# SOURCE #-} qualified GI.Gtk.Structs.TextAttributes as Gtk.TextAttributes
import {-# SOURCE #-} qualified GI.Gtk.Structs.TextIter as Gtk.TextIter
import {-# SOURCE #-} qualified GI.Gtk.Structs.WidgetPath as Gtk.WidgetPath
import qualified GI.Pango.Enums as Pango.Enums
import qualified GI.Pango.Objects.Context as Pango.Context
import qualified GI.Pango.Objects.FontMap as Pango.FontMap
import qualified GI.Pango.Objects.Layout as Pango.Layout
import qualified GI.Pango.Structs.FontDescription as Pango.FontDescription
import qualified GI.Pango.Structs.Language as Pango.Language
import qualified GI.Pango.Structs.TabArray as Pango.TabArray

#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Action as Gtk.Action
import {-# SOURCE #-} qualified GI.Gtk.Objects.ToggleAction as Gtk.ToggleAction

#endif

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

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

foreign import ccall "gtk_radio_action_get_type"
    c_gtk_radio_action_get_type :: IO B.Types.GType

instance B.Types.TypedObject RadioAction where
    glibType :: IO GType
glibType = IO GType
c_gtk_radio_action_get_type

instance B.Types.GObject RadioAction

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

instance O.HasParentTypes RadioAction
type instance O.ParentTypes RadioAction = '[Gtk.ToggleAction.ToggleAction, Gtk.Action.Action, GObject.Object.Object, Gtk.Buildable.Buildable]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveRadioActionMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveRadioActionMethod "activate" o = Gtk.Action.ActionActivateMethodInfo
    ResolveRadioActionMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolveRadioActionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveRadioActionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveRadioActionMethod "blockActivate" o = Gtk.Action.ActionBlockActivateMethodInfo
    ResolveRadioActionMethod "connectAccelerator" o = Gtk.Action.ActionConnectAcceleratorMethodInfo
    ResolveRadioActionMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveRadioActionMethod "createIcon" o = Gtk.Action.ActionCreateIconMethodInfo
    ResolveRadioActionMethod "createMenu" o = Gtk.Action.ActionCreateMenuMethodInfo
    ResolveRadioActionMethod "createMenuItem" o = Gtk.Action.ActionCreateMenuItemMethodInfo
    ResolveRadioActionMethod "createToolItem" o = Gtk.Action.ActionCreateToolItemMethodInfo
    ResolveRadioActionMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolveRadioActionMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolveRadioActionMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolveRadioActionMethod "disconnectAccelerator" o = Gtk.Action.ActionDisconnectAcceleratorMethodInfo
    ResolveRadioActionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveRadioActionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveRadioActionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveRadioActionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveRadioActionMethod "isSensitive" o = Gtk.Action.ActionIsSensitiveMethodInfo
    ResolveRadioActionMethod "isVisible" o = Gtk.Action.ActionIsVisibleMethodInfo
    ResolveRadioActionMethod "joinGroup" o = RadioActionJoinGroupMethodInfo
    ResolveRadioActionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveRadioActionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveRadioActionMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveRadioActionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveRadioActionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveRadioActionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveRadioActionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveRadioActionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveRadioActionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveRadioActionMethod "toggled" o = Gtk.ToggleAction.ToggleActionToggledMethodInfo
    ResolveRadioActionMethod "unblockActivate" o = Gtk.Action.ActionUnblockActivateMethodInfo
    ResolveRadioActionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveRadioActionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveRadioActionMethod "getAccelClosure" o = Gtk.Action.ActionGetAccelClosureMethodInfo
    ResolveRadioActionMethod "getAccelPath" o = Gtk.Action.ActionGetAccelPathMethodInfo
    ResolveRadioActionMethod "getActive" o = Gtk.ToggleAction.ToggleActionGetActiveMethodInfo
    ResolveRadioActionMethod "getAlwaysShowImage" o = Gtk.Action.ActionGetAlwaysShowImageMethodInfo
    ResolveRadioActionMethod "getCurrentValue" o = RadioActionGetCurrentValueMethodInfo
    ResolveRadioActionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveRadioActionMethod "getDrawAsRadio" o = Gtk.ToggleAction.ToggleActionGetDrawAsRadioMethodInfo
    ResolveRadioActionMethod "getGicon" o = Gtk.Action.ActionGetGiconMethodInfo
    ResolveRadioActionMethod "getGroup" o = RadioActionGetGroupMethodInfo
    ResolveRadioActionMethod "getIconName" o = Gtk.Action.ActionGetIconNameMethodInfo
    ResolveRadioActionMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolveRadioActionMethod "getIsImportant" o = Gtk.Action.ActionGetIsImportantMethodInfo
    ResolveRadioActionMethod "getLabel" o = Gtk.Action.ActionGetLabelMethodInfo
    ResolveRadioActionMethod "getName" o = Gtk.Action.ActionGetNameMethodInfo
    ResolveRadioActionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveRadioActionMethod "getProxies" o = Gtk.Action.ActionGetProxiesMethodInfo
    ResolveRadioActionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveRadioActionMethod "getSensitive" o = Gtk.Action.ActionGetSensitiveMethodInfo
    ResolveRadioActionMethod "getShortLabel" o = Gtk.Action.ActionGetShortLabelMethodInfo
    ResolveRadioActionMethod "getStockId" o = Gtk.Action.ActionGetStockIdMethodInfo
    ResolveRadioActionMethod "getTooltip" o = Gtk.Action.ActionGetTooltipMethodInfo
    ResolveRadioActionMethod "getVisible" o = Gtk.Action.ActionGetVisibleMethodInfo
    ResolveRadioActionMethod "getVisibleHorizontal" o = Gtk.Action.ActionGetVisibleHorizontalMethodInfo
    ResolveRadioActionMethod "getVisibleVertical" o = Gtk.Action.ActionGetVisibleVerticalMethodInfo
    ResolveRadioActionMethod "setAccelGroup" o = Gtk.Action.ActionSetAccelGroupMethodInfo
    ResolveRadioActionMethod "setAccelPath" o = Gtk.Action.ActionSetAccelPathMethodInfo
    ResolveRadioActionMethod "setActive" o = Gtk.ToggleAction.ToggleActionSetActiveMethodInfo
    ResolveRadioActionMethod "setAlwaysShowImage" o = Gtk.Action.ActionSetAlwaysShowImageMethodInfo
    ResolveRadioActionMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveRadioActionMethod "setCurrentValue" o = RadioActionSetCurrentValueMethodInfo
    ResolveRadioActionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveRadioActionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveRadioActionMethod "setDrawAsRadio" o = Gtk.ToggleAction.ToggleActionSetDrawAsRadioMethodInfo
    ResolveRadioActionMethod "setGicon" o = Gtk.Action.ActionSetGiconMethodInfo
    ResolveRadioActionMethod "setGroup" o = RadioActionSetGroupMethodInfo
    ResolveRadioActionMethod "setIconName" o = Gtk.Action.ActionSetIconNameMethodInfo
    ResolveRadioActionMethod "setIsImportant" o = Gtk.Action.ActionSetIsImportantMethodInfo
    ResolveRadioActionMethod "setLabel" o = Gtk.Action.ActionSetLabelMethodInfo
    ResolveRadioActionMethod "setName" o = Gtk.Buildable.BuildableSetNameMethodInfo
    ResolveRadioActionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveRadioActionMethod "setSensitive" o = Gtk.Action.ActionSetSensitiveMethodInfo
    ResolveRadioActionMethod "setShortLabel" o = Gtk.Action.ActionSetShortLabelMethodInfo
    ResolveRadioActionMethod "setStockId" o = Gtk.Action.ActionSetStockIdMethodInfo
    ResolveRadioActionMethod "setTooltip" o = Gtk.Action.ActionSetTooltipMethodInfo
    ResolveRadioActionMethod "setVisible" o = Gtk.Action.ActionSetVisibleMethodInfo
    ResolveRadioActionMethod "setVisibleHorizontal" o = Gtk.Action.ActionSetVisibleHorizontalMethodInfo
    ResolveRadioActionMethod "setVisibleVertical" o = Gtk.Action.ActionSetVisibleVerticalMethodInfo
    ResolveRadioActionMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- signal RadioAction::changed
{-# DEPRECATED RadioActionChangedCallback ["(Since version 3.10)"] #-}
-- | The [changed](#g:signal:changed) signal is emitted on every member of a radio group when the
-- active member is changed. The signal gets emitted after the [activate](#g:signal:activate) signals
-- for the previous and current active members.
-- 
-- /Since: 2.4/
type RadioActionChangedCallback =
    RadioAction
    -- ^ /@current@/: the member of /@action@/\'s group which has just been activated
    -> IO ()

type C_RadioActionChangedCallback =
    Ptr RadioAction ->                      -- object
    Ptr RadioAction ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_RadioActionChangedCallback :: 
    GObject a => (a -> RadioActionChangedCallback) ->
    C_RadioActionChangedCallback
wrap_RadioActionChangedCallback :: forall a.
GObject a =>
(a -> RadioActionChangedCallback) -> C_RadioActionChangedCallback
wrap_RadioActionChangedCallback a -> RadioActionChangedCallback
gi'cb Ptr RadioAction
gi'selfPtr Ptr RadioAction
current Ptr ()
_ = do
    RadioAction
current' <- ((ManagedPtr RadioAction -> RadioAction)
-> Ptr RadioAction -> IO RadioAction
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr RadioAction -> RadioAction
RadioAction) Ptr RadioAction
current
    Ptr RadioAction -> RadioActionChangedCallback -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr RadioAction
gi'selfPtr (RadioActionChangedCallback -> IO ())
-> RadioActionChangedCallback -> IO ()
forall a b. (a -> b) -> a -> b
$ \RadioAction
gi'self -> a -> RadioActionChangedCallback
gi'cb (RadioAction -> a
forall a b. Coercible a b => a -> b
Coerce.coerce RadioAction
gi'self)  RadioAction
current'


-- | Connect a signal handler for the [changed](#signal:changed) 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' radioAction #changed callback
-- @
-- 
-- 
onRadioActionChanged :: (IsRadioAction a, MonadIO m) => a -> ((?self :: a) => RadioActionChangedCallback) -> m SignalHandlerId
onRadioActionChanged :: forall a (m :: * -> *).
(IsRadioAction a, MonadIO m) =>
a
-> ((?self::a) => RadioActionChangedCallback) -> m SignalHandlerId
onRadioActionChanged a
obj (?self::a) => RadioActionChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> RadioActionChangedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => RadioActionChangedCallback
RadioActionChangedCallback
cb
    let wrapped' :: C_RadioActionChangedCallback
wrapped' = (a -> RadioActionChangedCallback) -> C_RadioActionChangedCallback
forall a.
GObject a =>
(a -> RadioActionChangedCallback) -> C_RadioActionChangedCallback
wrap_RadioActionChangedCallback a -> RadioActionChangedCallback
wrapped
    FunPtr C_RadioActionChangedCallback
wrapped'' <- C_RadioActionChangedCallback
-> IO (FunPtr C_RadioActionChangedCallback)
mk_RadioActionChangedCallback C_RadioActionChangedCallback
wrapped'
    a
-> Text
-> FunPtr C_RadioActionChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"changed" FunPtr C_RadioActionChangedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [changed](#signal:changed) 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' radioAction #changed 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.
-- 
afterRadioActionChanged :: (IsRadioAction a, MonadIO m) => a -> ((?self :: a) => RadioActionChangedCallback) -> m SignalHandlerId
afterRadioActionChanged :: forall a (m :: * -> *).
(IsRadioAction a, MonadIO m) =>
a
-> ((?self::a) => RadioActionChangedCallback) -> m SignalHandlerId
afterRadioActionChanged a
obj (?self::a) => RadioActionChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> RadioActionChangedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => RadioActionChangedCallback
RadioActionChangedCallback
cb
    let wrapped' :: C_RadioActionChangedCallback
wrapped' = (a -> RadioActionChangedCallback) -> C_RadioActionChangedCallback
forall a.
GObject a =>
(a -> RadioActionChangedCallback) -> C_RadioActionChangedCallback
wrap_RadioActionChangedCallback a -> RadioActionChangedCallback
wrapped
    FunPtr C_RadioActionChangedCallback
wrapped'' <- C_RadioActionChangedCallback
-> IO (FunPtr C_RadioActionChangedCallback)
mk_RadioActionChangedCallback C_RadioActionChangedCallback
wrapped'
    a
-> Text
-> FunPtr C_RadioActionChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"changed" FunPtr C_RadioActionChangedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data RadioActionChangedSignalInfo
instance SignalInfo RadioActionChangedSignalInfo where
    type HaskellCallbackType RadioActionChangedSignalInfo = RadioActionChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_RadioActionChangedCallback cb
        cb'' <- mk_RadioActionChangedCallback cb'
        connectSignalFunPtr obj "changed" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.RadioAction::changed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-RadioAction.html#g:signal:changed"})

#endif

-- VVV Prop "current-value"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@current-value@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' radioAction #currentValue
-- @
getRadioActionCurrentValue :: (MonadIO m, IsRadioAction o) => o -> m Int32
getRadioActionCurrentValue :: forall (m :: * -> *) o.
(MonadIO m, IsRadioAction o) =>
o -> m Int32
getRadioActionCurrentValue 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
"current-value"

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

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

#if defined(ENABLE_OVERLOADING)
data RadioActionCurrentValuePropertyInfo
instance AttrInfo RadioActionCurrentValuePropertyInfo where
    type AttrAllowedOps RadioActionCurrentValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint RadioActionCurrentValuePropertyInfo = IsRadioAction
    type AttrSetTypeConstraint RadioActionCurrentValuePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint RadioActionCurrentValuePropertyInfo = (~) Int32
    type AttrTransferType RadioActionCurrentValuePropertyInfo = Int32
    type AttrGetType RadioActionCurrentValuePropertyInfo = Int32
    type AttrLabel RadioActionCurrentValuePropertyInfo = "current-value"
    type AttrOrigin RadioActionCurrentValuePropertyInfo = RadioAction
    attrGet = getRadioActionCurrentValue
    attrSet = setRadioActionCurrentValue
    attrTransfer _ v = do
        return v
    attrConstruct = constructRadioActionCurrentValue
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.RadioAction.currentValue"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-RadioAction.html#g:attr:currentValue"
        })
#endif

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

-- | 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' radioAction [ #group 'Data.GI.Base.Attributes.:=' value ]
-- @
setRadioActionGroup :: (MonadIO m, IsRadioAction o, IsRadioAction a) => o -> a -> m ()
setRadioActionGroup :: forall (m :: * -> *) o a.
(MonadIO m, IsRadioAction o, IsRadioAction a) =>
o -> a -> m ()
setRadioActionGroup o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"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`.
constructRadioActionGroup :: (IsRadioAction o, MIO.MonadIO m, IsRadioAction a) => a -> m (GValueConstruct o)
constructRadioActionGroup :: forall o (m :: * -> *) a.
(IsRadioAction o, MonadIO m, IsRadioAction a) =>
a -> m (GValueConstruct o)
constructRadioActionGroup a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"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
-- @
clearRadioActionGroup :: (MonadIO m, IsRadioAction o) => o -> m ()
clearRadioActionGroup :: forall (m :: * -> *) o. (MonadIO m, IsRadioAction o) => o -> m ()
clearRadioActionGroup o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe RadioAction -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"group" (Maybe RadioAction
forall a. Maybe a
Nothing :: Maybe RadioAction)

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

-- VVV Prop "value"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

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

#if defined(ENABLE_OVERLOADING)
data RadioActionValuePropertyInfo
instance AttrInfo RadioActionValuePropertyInfo where
    type AttrAllowedOps RadioActionValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint RadioActionValuePropertyInfo = IsRadioAction
    type AttrSetTypeConstraint RadioActionValuePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint RadioActionValuePropertyInfo = (~) Int32
    type AttrTransferType RadioActionValuePropertyInfo = Int32
    type AttrGetType RadioActionValuePropertyInfo = Int32
    type AttrLabel RadioActionValuePropertyInfo = "value"
    type AttrOrigin RadioActionValuePropertyInfo = RadioAction
    attrGet = getRadioActionValue
    attrSet = setRadioActionValue
    attrTransfer _ v = do
        return v
    attrConstruct = constructRadioActionValue
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.RadioAction.value"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-RadioAction.html#g:attr:value"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList RadioAction
type instance O.AttributeList RadioAction = RadioActionAttributeList
type RadioActionAttributeList = ('[ '("actionGroup", Gtk.Action.ActionActionGroupPropertyInfo), '("active", Gtk.ToggleAction.ToggleActionActivePropertyInfo), '("alwaysShowImage", Gtk.Action.ActionAlwaysShowImagePropertyInfo), '("currentValue", RadioActionCurrentValuePropertyInfo), '("drawAsRadio", Gtk.ToggleAction.ToggleActionDrawAsRadioPropertyInfo), '("gicon", Gtk.Action.ActionGiconPropertyInfo), '("group", RadioActionGroupPropertyInfo), '("hideIfEmpty", Gtk.Action.ActionHideIfEmptyPropertyInfo), '("iconName", Gtk.Action.ActionIconNamePropertyInfo), '("isImportant", Gtk.Action.ActionIsImportantPropertyInfo), '("label", Gtk.Action.ActionLabelPropertyInfo), '("name", Gtk.Action.ActionNamePropertyInfo), '("sensitive", Gtk.Action.ActionSensitivePropertyInfo), '("shortLabel", Gtk.Action.ActionShortLabelPropertyInfo), '("stockId", Gtk.Action.ActionStockIdPropertyInfo), '("tooltip", Gtk.Action.ActionTooltipPropertyInfo), '("value", RadioActionValuePropertyInfo), '("visible", Gtk.Action.ActionVisiblePropertyInfo), '("visibleHorizontal", Gtk.Action.ActionVisibleHorizontalPropertyInfo), '("visibleOverflown", Gtk.Action.ActionVisibleOverflownPropertyInfo), '("visibleVertical", Gtk.Action.ActionVisibleVerticalPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
radioActionCurrentValue :: AttrLabelProxy "currentValue"
radioActionCurrentValue = AttrLabelProxy

radioActionGroup :: AttrLabelProxy "group"
radioActionGroup = AttrLabelProxy

radioActionValue :: AttrLabelProxy "value"
radioActionValue = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList RadioAction = RadioActionSignalList
type RadioActionSignalList = ('[ '("activate", Gtk.Action.ActionActivateSignalInfo), '("changed", RadioActionChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("toggled", Gtk.ToggleAction.ToggleActionToggledSignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method RadioAction::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A unique name for the action"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The label displayed in menu items and on buttons,\n  or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "tooltip"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A tooltip for this action, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stock_id"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The stock icon to display in widgets representing\n  this action, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The value which gtk_radio_action_get_current_value() should\n  return if this action is selected."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "RadioAction" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_radio_action_new" gtk_radio_action_new :: 
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- label : TBasicType TUTF8
    CString ->                              -- tooltip : TBasicType TUTF8
    CString ->                              -- stock_id : TBasicType TUTF8
    Int32 ->                                -- value : TBasicType TInt
    IO (Ptr RadioAction)

{-# DEPRECATED radioActionNew ["(Since version 3.10)"] #-}
-- | Creates a new t'GI.Gtk.Objects.RadioAction.RadioAction' object. To add the action to
-- a t'GI.Gtk.Objects.ActionGroup.ActionGroup' and set the accelerator for the action,
-- call 'GI.Gtk.Objects.ActionGroup.actionGroupAddActionWithAccel'.
-- 
-- /Since: 2.4/
radioActionNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@name@/: A unique name for the action
    -> Maybe (T.Text)
    -- ^ /@label@/: The label displayed in menu items and on buttons,
    --   or 'P.Nothing'
    -> Maybe (T.Text)
    -- ^ /@tooltip@/: A tooltip for this action, or 'P.Nothing'
    -> Maybe (T.Text)
    -- ^ /@stockId@/: The stock icon to display in widgets representing
    --   this action, or 'P.Nothing'
    -> Int32
    -- ^ /@value@/: The value which 'GI.Gtk.Objects.RadioAction.radioActionGetCurrentValue' should
    --   return if this action is selected.
    -> m RadioAction
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.RadioAction.RadioAction'
radioActionNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text
-> Maybe Text -> Maybe Text -> Maybe Text -> Int32 -> m RadioAction
radioActionNew Text
name Maybe Text
label Maybe Text
tooltip Maybe Text
stockId Int32
value = IO RadioAction -> m RadioAction
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RadioAction -> m RadioAction)
-> IO RadioAction -> m RadioAction
forall a b. (a -> b) -> a -> b
$ do
    CString
name' <- Text -> IO CString
textToCString Text
name
    CString
maybeLabel <- case Maybe Text
label of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
FP.nullPtr
        Just Text
jLabel -> do
            CString
jLabel' <- Text -> IO CString
textToCString Text
jLabel
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jLabel'
    CString
maybeTooltip <- case Maybe Text
tooltip of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
FP.nullPtr
        Just Text
jTooltip -> do
            CString
jTooltip' <- Text -> IO CString
textToCString Text
jTooltip
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jTooltip'
    CString
maybeStockId <- case Maybe Text
stockId of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
FP.nullPtr
        Just Text
jStockId -> do
            CString
jStockId' <- Text -> IO CString
textToCString Text
jStockId
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jStockId'
    Ptr RadioAction
result <- CString
-> CString -> CString -> CString -> Int32 -> IO (Ptr RadioAction)
gtk_radio_action_new CString
name' CString
maybeLabel CString
maybeTooltip CString
maybeStockId Int32
value
    Text -> Ptr RadioAction -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"radioActionNew" Ptr RadioAction
result
    RadioAction
result' <- ((ManagedPtr RadioAction -> RadioAction)
-> Ptr RadioAction -> IO RadioAction
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr RadioAction -> RadioAction
RadioAction) Ptr RadioAction
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeLabel
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeTooltip
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeStockId
    RadioAction -> IO RadioAction
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return RadioAction
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method RadioAction::get_current_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RadioAction" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRadioAction" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_radio_action_get_current_value" gtk_radio_action_get_current_value :: 
    Ptr RadioAction ->                      -- action : TInterface (Name {namespace = "Gtk", name = "RadioAction"})
    IO Int32

{-# DEPRECATED radioActionGetCurrentValue ["(Since version 3.10)"] #-}
-- | Obtains the value property of the currently active member of
-- the group to which /@action@/ belongs.
-- 
-- /Since: 2.4/
radioActionGetCurrentValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsRadioAction a) =>
    a
    -- ^ /@action@/: a t'GI.Gtk.Objects.RadioAction.RadioAction'
    -> m Int32
    -- ^ __Returns:__ The value of the currently active group member
radioActionGetCurrentValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRadioAction a) =>
a -> m Int32
radioActionGetCurrentValue a
action = 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 RadioAction
action' <- a -> IO (Ptr RadioAction)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
    Int32
result <- Ptr RadioAction -> IO Int32
gtk_radio_action_get_current_value Ptr RadioAction
action'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data RadioActionGetCurrentValueMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsRadioAction a) => O.OverloadedMethod RadioActionGetCurrentValueMethodInfo a signature where
    overloadedMethod = radioActionGetCurrentValue

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


#endif

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

foreign import ccall "gtk_radio_action_get_group" gtk_radio_action_get_group :: 
    Ptr RadioAction ->                      -- action : TInterface (Name {namespace = "Gtk", name = "RadioAction"})
    IO (Ptr (GSList (Ptr RadioAction)))

{-# DEPRECATED radioActionGetGroup ["(Since version 3.10)"] #-}
-- | Returns the list representing the radio group for this object.
-- Note that the returned list is only valid until the next change
-- to the group.
-- 
-- A common way to set up a group of radio group is the following:
-- 
-- === /C code/
-- >
-- >  GSList *group = NULL;
-- >  GtkRadioAction *action;
-- > 
-- >  while ( ...more actions to add... /)
-- >    {
-- >       action = gtk_radio_action_new (...);
-- >       
-- >       gtk_radio_action_set_group (action, group);
-- >       group = gtk_radio_action_get_group (action);
-- >    }
-- 
-- 
-- /Since: 2.4/
radioActionGetGroup ::
    (B.CallStack.HasCallStack, MonadIO m, IsRadioAction a) =>
    a
    -- ^ /@action@/: the action object
    -> m [RadioAction]
    -- ^ __Returns:__ the list representing the radio group for this object
radioActionGetGroup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRadioAction a) =>
a -> m [RadioAction]
radioActionGetGroup a
action = IO [RadioAction] -> m [RadioAction]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [RadioAction] -> m [RadioAction])
-> IO [RadioAction] -> m [RadioAction]
forall a b. (a -> b) -> a -> b
$ do
    Ptr RadioAction
action' <- a -> IO (Ptr RadioAction)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
    Ptr (GSList (Ptr RadioAction))
result <- Ptr RadioAction -> IO (Ptr (GSList (Ptr RadioAction)))
gtk_radio_action_get_group Ptr RadioAction
action'
    [Ptr RadioAction]
result' <- Ptr (GSList (Ptr RadioAction)) -> IO [Ptr RadioAction]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr RadioAction))
result
    [RadioAction]
result'' <- (Ptr RadioAction -> IO RadioAction)
-> [Ptr RadioAction] -> IO [RadioAction]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr RadioAction -> RadioAction)
-> Ptr RadioAction -> IO RadioAction
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr RadioAction -> RadioAction
RadioAction) [Ptr RadioAction]
result'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
    [RadioAction] -> IO [RadioAction]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [RadioAction]
result''

#if defined(ENABLE_OVERLOADING)
data RadioActionGetGroupMethodInfo
instance (signature ~ (m [RadioAction]), MonadIO m, IsRadioAction a) => O.OverloadedMethod RadioActionGetGroupMethodInfo a signature where
    overloadedMethod = radioActionGetGroup

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


#endif

-- method RadioAction::join_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RadioAction" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the action object" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_source"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RadioAction" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a radio action object whos group we are\n  joining, or %NULL to remove the radio action from its group"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_radio_action_join_group" gtk_radio_action_join_group :: 
    Ptr RadioAction ->                      -- action : TInterface (Name {namespace = "Gtk", name = "RadioAction"})
    Ptr RadioAction ->                      -- group_source : TInterface (Name {namespace = "Gtk", name = "RadioAction"})
    IO ()

{-# DEPRECATED radioActionJoinGroup ["(Since version 3.10)"] #-}
-- | Joins a radio action object to the group of another radio action object.
-- 
-- Use this in language bindings instead of the 'GI.Gtk.Objects.RadioAction.radioActionGetGroup'
-- and 'GI.Gtk.Objects.RadioAction.radioActionSetGroup' methods
-- 
-- A common way to set up a group of radio actions is the following:
-- 
-- === /C code/
-- >
-- >  GtkRadioAction *action;
-- >  GtkRadioAction *last_action;
-- > 
-- >  while ( ...more actions to add... /)
-- >    {
-- >       action = gtk_radio_action_new (...);
-- >       
-- >       gtk_radio_action_join_group (action, last_action);
-- >       last_action = action;
-- >    }
-- 
-- 
-- /Since: 3.0/
radioActionJoinGroup ::
    (B.CallStack.HasCallStack, MonadIO m, IsRadioAction a, IsRadioAction b) =>
    a
    -- ^ /@action@/: the action object
    -> Maybe (b)
    -- ^ /@groupSource@/: a radio action object whos group we are
    --   joining, or 'P.Nothing' to remove the radio action from its group
    -> m ()
radioActionJoinGroup :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRadioAction a, IsRadioAction b) =>
a -> Maybe b -> m ()
radioActionJoinGroup a
action Maybe b
groupSource = 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 RadioAction
action' <- a -> IO (Ptr RadioAction)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
    Ptr RadioAction
maybeGroupSource <- case Maybe b
groupSource of
        Maybe b
Nothing -> Ptr RadioAction -> IO (Ptr RadioAction)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr RadioAction
forall a. Ptr a
FP.nullPtr
        Just b
jGroupSource -> do
            Ptr RadioAction
jGroupSource' <- b -> IO (Ptr RadioAction)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jGroupSource
            Ptr RadioAction -> IO (Ptr RadioAction)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr RadioAction
jGroupSource'
    Ptr RadioAction -> Ptr RadioAction -> IO ()
gtk_radio_action_join_group Ptr RadioAction
action' Ptr RadioAction
maybeGroupSource
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
groupSource 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 RadioActionJoinGroupMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsRadioAction a, IsRadioAction b) => O.OverloadedMethod RadioActionJoinGroupMethodInfo a signature where
    overloadedMethod = radioActionJoinGroup

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


#endif

-- method RadioAction::set_current_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RadioAction" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRadioAction" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "current_value"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new value" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_radio_action_set_current_value" gtk_radio_action_set_current_value :: 
    Ptr RadioAction ->                      -- action : TInterface (Name {namespace = "Gtk", name = "RadioAction"})
    Int32 ->                                -- current_value : TBasicType TInt
    IO ()

{-# DEPRECATED radioActionSetCurrentValue ["(Since version 3.10)"] #-}
-- | Sets the currently active group member to the member with value
-- property /@currentValue@/.
-- 
-- /Since: 2.10/
radioActionSetCurrentValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsRadioAction a) =>
    a
    -- ^ /@action@/: a t'GI.Gtk.Objects.RadioAction.RadioAction'
    -> Int32
    -- ^ /@currentValue@/: the new value
    -> m ()
radioActionSetCurrentValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRadioAction a) =>
a -> Int32 -> m ()
radioActionSetCurrentValue a
action Int32
currentValue = 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 RadioAction
action' <- a -> IO (Ptr RadioAction)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
    Ptr RadioAction -> Int32 -> IO ()
gtk_radio_action_set_current_value Ptr RadioAction
action' Int32
currentValue
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RadioActionSetCurrentValueMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsRadioAction a) => O.OverloadedMethod RadioActionSetCurrentValueMethodInfo a signature where
    overloadedMethod = radioActionSetCurrentValue

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


#endif

-- method RadioAction::set_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "action"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RadioAction" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the action object" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group"
--           , argType =
--               TGSList
--                 (TInterface Name { namespace = "Gtk" , name = "RadioAction" })
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a list representing a radio group, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_radio_action_set_group" gtk_radio_action_set_group :: 
    Ptr RadioAction ->                      -- action : TInterface (Name {namespace = "Gtk", name = "RadioAction"})
    Ptr (GSList (Ptr RadioAction)) ->       -- group : TGSList (TInterface (Name {namespace = "Gtk", name = "RadioAction"}))
    IO ()

{-# DEPRECATED radioActionSetGroup ["(Since version 3.10)"] #-}
-- | Sets the radio group for the radio action object.
-- 
-- /Since: 2.4/
radioActionSetGroup ::
    (B.CallStack.HasCallStack, MonadIO m, IsRadioAction a, IsRadioAction b) =>
    a
    -- ^ /@action@/: the action object
    -> [b]
    -- ^ /@group@/: a list representing a radio group, or 'P.Nothing'
    -> m ()
radioActionSetGroup :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRadioAction a, IsRadioAction b) =>
a -> [b] -> m ()
radioActionSetGroup a
action [b]
group = 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 RadioAction
action' <- a -> IO (Ptr RadioAction)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
    [Ptr RadioAction]
group' <- (b -> IO (Ptr RadioAction)) -> [b] -> IO [Ptr RadioAction]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM b -> IO (Ptr RadioAction)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr [b]
group
    Ptr (GSList (Ptr RadioAction))
group'' <- [Ptr RadioAction] -> IO (Ptr (GSList (Ptr RadioAction)))
forall a. [Ptr a] -> IO (Ptr (GSList (Ptr a)))
packGSList [Ptr RadioAction]
group'
    Ptr RadioAction -> Ptr (GSList (Ptr RadioAction)) -> IO ()
gtk_radio_action_set_group Ptr RadioAction
action' Ptr (GSList (Ptr RadioAction))
group''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
    (b -> IO ()) -> [b] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [b]
group
    Ptr (GSList (Ptr RadioAction)) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free Ptr (GSList (Ptr RadioAction))
group''
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RadioActionSetGroupMethodInfo
instance (signature ~ ([b] -> m ()), MonadIO m, IsRadioAction a, IsRadioAction b) => O.OverloadedMethod RadioActionSetGroupMethodInfo a signature where
    overloadedMethod = radioActionSetGroup

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


#endif