{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.Gtk.Objects.RadioAction
    ( 

-- * Exported types
    RadioAction(..)                         ,
    RadioActionK                            ,
    toRadioAction                           ,
    noRadioAction                           ,


 -- * Methods
-- ** radioActionGetCurrentValue
    radioActionGetCurrentValue              ,


-- ** radioActionGetGroup
    radioActionGetGroup                     ,


-- ** radioActionJoinGroup
    radioActionJoinGroup                    ,


-- ** radioActionNew
    radioActionNew                          ,


-- ** radioActionSetCurrentValue
    radioActionSetCurrentValue              ,


-- ** radioActionSetGroup
    radioActionSetGroup                     ,




 -- * Properties
-- ** CurrentValue
    RadioActionCurrentValuePropertyInfo     ,
    constructRadioActionCurrentValue        ,
    getRadioActionCurrentValue              ,
    setRadioActionCurrentValue              ,


-- ** Group
    RadioActionGroupPropertyInfo            ,
    constructRadioActionGroup               ,
    setRadioActionGroup                     ,


-- ** Value
    RadioActionValuePropertyInfo            ,
    constructRadioActionValue               ,
    getRadioActionValue                     ,
    setRadioActionValue                     ,




 -- * Signals
-- ** Changed
    RadioActionChangedCallback              ,
    RadioActionChangedCallbackC             ,
    RadioActionChangedSignalInfo            ,
    afterRadioActionChanged                 ,
    mkRadioActionChangedCallback            ,
    noRadioActionChangedCallback            ,
    onRadioActionChanged                    ,
    radioActionChangedCallbackWrapper       ,
    radioActionChangedClosure               ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Gtk.Types
import GI.Gtk.Callbacks
import qualified GI.GObject as GObject

newtype RadioAction = RadioAction (ForeignPtr RadioAction)
foreign import ccall "gtk_radio_action_get_type"
    c_gtk_radio_action_get_type :: IO GType

type instance ParentTypes RadioAction = RadioActionParentTypes
type RadioActionParentTypes = '[ToggleAction, Action, GObject.Object, Buildable]

instance GObject RadioAction where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_gtk_radio_action_get_type
    

class GObject o => RadioActionK o
instance (GObject o, IsDescendantOf RadioAction o) => RadioActionK o

toRadioAction :: RadioActionK o => o -> IO RadioAction
toRadioAction = unsafeCastTo RadioAction

noRadioAction :: Maybe RadioAction
noRadioAction = Nothing

-- signal RadioAction::changed
type RadioActionChangedCallback =
    RadioAction ->
    IO ()

noRadioActionChangedCallback :: Maybe RadioActionChangedCallback
noRadioActionChangedCallback = Nothing

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

foreign import ccall "wrapper"
    mkRadioActionChangedCallback :: RadioActionChangedCallbackC -> IO (FunPtr RadioActionChangedCallbackC)

radioActionChangedClosure :: RadioActionChangedCallback -> IO Closure
radioActionChangedClosure cb = newCClosure =<< mkRadioActionChangedCallback wrapped
    where wrapped = radioActionChangedCallbackWrapper cb

radioActionChangedCallbackWrapper ::
    RadioActionChangedCallback ->
    Ptr () ->
    Ptr RadioAction ->
    Ptr () ->
    IO ()
radioActionChangedCallbackWrapper _cb _ current _ = do
    current' <- (newObject RadioAction) current
    _cb  current'

onRadioActionChanged :: (GObject a, MonadIO m) => a -> RadioActionChangedCallback -> m SignalHandlerId
onRadioActionChanged obj cb = liftIO $ connectRadioActionChanged obj cb SignalConnectBefore
afterRadioActionChanged :: (GObject a, MonadIO m) => a -> RadioActionChangedCallback -> m SignalHandlerId
afterRadioActionChanged obj cb = connectRadioActionChanged obj cb SignalConnectAfter

connectRadioActionChanged :: (GObject a, MonadIO m) =>
                             a -> RadioActionChangedCallback -> SignalConnectMode -> m SignalHandlerId
connectRadioActionChanged obj cb after = liftIO $ do
    cb' <- mkRadioActionChangedCallback (radioActionChangedCallbackWrapper cb)
    connectSignalFunPtr obj "changed" cb' after

-- VVV Prop "current-value"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getRadioActionCurrentValue :: (MonadIO m, RadioActionK o) => o -> m Int32
getRadioActionCurrentValue obj = liftIO $ getObjectPropertyCInt obj "current-value"

setRadioActionCurrentValue :: (MonadIO m, RadioActionK o) => o -> Int32 -> m ()
setRadioActionCurrentValue obj val = liftIO $ setObjectPropertyCInt obj "current-value" val

constructRadioActionCurrentValue :: Int32 -> IO ([Char], GValue)
constructRadioActionCurrentValue val = constructObjectPropertyCInt "current-value" val

data RadioActionCurrentValuePropertyInfo
instance AttrInfo RadioActionCurrentValuePropertyInfo where
    type AttrAllowedOps RadioActionCurrentValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint RadioActionCurrentValuePropertyInfo = (~) Int32
    type AttrBaseTypeConstraint RadioActionCurrentValuePropertyInfo = RadioActionK
    type AttrGetType RadioActionCurrentValuePropertyInfo = Int32
    type AttrLabel RadioActionCurrentValuePropertyInfo = "RadioAction::current-value"
    attrGet _ = getRadioActionCurrentValue
    attrSet _ = setRadioActionCurrentValue
    attrConstruct _ = constructRadioActionCurrentValue

-- VVV Prop "group"
   -- Type: TInterface "Gtk" "RadioAction"
   -- Flags: [PropertyWritable]

setRadioActionGroup :: (MonadIO m, RadioActionK o, RadioActionK a) => o -> a -> m ()
setRadioActionGroup obj val = liftIO $ setObjectPropertyObject obj "group" val

constructRadioActionGroup :: (RadioActionK a) => a -> IO ([Char], GValue)
constructRadioActionGroup val = constructObjectPropertyObject "group" val

data RadioActionGroupPropertyInfo
instance AttrInfo RadioActionGroupPropertyInfo where
    type AttrAllowedOps RadioActionGroupPropertyInfo = '[ 'AttrSet, 'AttrConstruct]
    type AttrSetTypeConstraint RadioActionGroupPropertyInfo = RadioActionK
    type AttrBaseTypeConstraint RadioActionGroupPropertyInfo = RadioActionK
    type AttrGetType RadioActionGroupPropertyInfo = ()
    type AttrLabel RadioActionGroupPropertyInfo = "RadioAction::group"
    attrGet _ = undefined
    attrSet _ = setRadioActionGroup
    attrConstruct _ = constructRadioActionGroup

-- VVV Prop "value"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getRadioActionValue :: (MonadIO m, RadioActionK o) => o -> m Int32
getRadioActionValue obj = liftIO $ getObjectPropertyCInt obj "value"

setRadioActionValue :: (MonadIO m, RadioActionK o) => o -> Int32 -> m ()
setRadioActionValue obj val = liftIO $ setObjectPropertyCInt obj "value" val

constructRadioActionValue :: Int32 -> IO ([Char], GValue)
constructRadioActionValue val = constructObjectPropertyCInt "value" val

data RadioActionValuePropertyInfo
instance AttrInfo RadioActionValuePropertyInfo where
    type AttrAllowedOps RadioActionValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint RadioActionValuePropertyInfo = (~) Int32
    type AttrBaseTypeConstraint RadioActionValuePropertyInfo = RadioActionK
    type AttrGetType RadioActionValuePropertyInfo = Int32
    type AttrLabel RadioActionValuePropertyInfo = "RadioAction::value"
    attrGet _ = getRadioActionValue
    attrSet _ = setRadioActionValue
    attrConstruct _ = constructRadioActionValue

type instance AttributeList RadioAction = RadioActionAttributeList
type RadioActionAttributeList = ('[ '("action-group", ActionActionGroupPropertyInfo), '("active", ToggleActionActivePropertyInfo), '("always-show-image", ActionAlwaysShowImagePropertyInfo), '("current-value", RadioActionCurrentValuePropertyInfo), '("draw-as-radio", ToggleActionDrawAsRadioPropertyInfo), '("gicon", ActionGiconPropertyInfo), '("group", RadioActionGroupPropertyInfo), '("hide-if-empty", ActionHideIfEmptyPropertyInfo), '("icon-name", ActionIconNamePropertyInfo), '("is-important", ActionIsImportantPropertyInfo), '("label", ActionLabelPropertyInfo), '("name", ActionNamePropertyInfo), '("sensitive", ActionSensitivePropertyInfo), '("short-label", ActionShortLabelPropertyInfo), '("stock-id", ActionStockIdPropertyInfo), '("tooltip", ActionTooltipPropertyInfo), '("value", RadioActionValuePropertyInfo), '("visible", ActionVisiblePropertyInfo), '("visible-horizontal", ActionVisibleHorizontalPropertyInfo), '("visible-overflown", ActionVisibleOverflownPropertyInfo), '("visible-vertical", ActionVisibleVerticalPropertyInfo)] :: [(Symbol, *)])

data RadioActionChangedSignalInfo
instance SignalInfo RadioActionChangedSignalInfo where
    type HaskellCallbackType RadioActionChangedSignalInfo = RadioActionChangedCallback
    connectSignal _ = connectRadioActionChanged

type instance SignalList RadioAction = RadioActionSignalList
type RadioActionSignalList = ('[ '("activate", ActionActivateSignalInfo), '("changed", RadioActionChangedSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("toggled", ToggleActionToggledSignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method RadioAction::new
-- method type : Constructor
-- Args : [Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "label", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tooltip", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stock_id", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "label", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tooltip", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stock_id", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "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 TInt32
    IO (Ptr RadioAction)

{-# DEPRECATED radioActionNew ["(Since version 3.10)"]#-}
radioActionNew ::
    (MonadIO m) =>
    T.Text ->                               -- name
    Maybe (T.Text) ->                       -- label
    Maybe (T.Text) ->                       -- tooltip
    Maybe (T.Text) ->                       -- stock_id
    Int32 ->                                -- value
    m RadioAction
radioActionNew name label tooltip stock_id value = liftIO $ do
    name' <- textToCString name
    maybeLabel <- case label of
        Nothing -> return nullPtr
        Just jLabel -> do
            jLabel' <- textToCString jLabel
            return jLabel'
    maybeTooltip <- case tooltip of
        Nothing -> return nullPtr
        Just jTooltip -> do
            jTooltip' <- textToCString jTooltip
            return jTooltip'
    maybeStock_id <- case stock_id of
        Nothing -> return nullPtr
        Just jStock_id -> do
            jStock_id' <- textToCString jStock_id
            return jStock_id'
    result <- gtk_radio_action_new name' maybeLabel maybeTooltip maybeStock_id value
    checkUnexpectedReturnNULL "gtk_radio_action_new" result
    result' <- (wrapObject RadioAction) result
    freeMem name'
    freeMem maybeLabel
    freeMem maybeTooltip
    freeMem maybeStock_id
    return result'

-- method RadioAction::get_current_value
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RadioAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RadioAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "gtk_radio_action_get_current_value" gtk_radio_action_get_current_value :: 
    Ptr RadioAction ->                      -- _obj : TInterface "Gtk" "RadioAction"
    IO Int32

{-# DEPRECATED radioActionGetCurrentValue ["(Since version 3.10)"]#-}
radioActionGetCurrentValue ::
    (MonadIO m, RadioActionK a) =>
    a ->                                    -- _obj
    m Int32
radioActionGetCurrentValue _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_radio_action_get_current_value _obj'
    touchManagedPtr _obj
    return result

-- method RadioAction::get_group
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RadioAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RadioAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TGSList (TInterface "Gtk" "RadioAction")
-- throws : False
-- Skip return : False

foreign import ccall "gtk_radio_action_get_group" gtk_radio_action_get_group :: 
    Ptr RadioAction ->                      -- _obj : TInterface "Gtk" "RadioAction"
    IO (Ptr (GSList (Ptr RadioAction)))

{-# DEPRECATED radioActionGetGroup ["(Since version 3.10)"]#-}
radioActionGetGroup ::
    (MonadIO m, RadioActionK a) =>
    a ->                                    -- _obj
    m [RadioAction]
radioActionGetGroup _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_radio_action_get_group _obj'
    checkUnexpectedReturnNULL "gtk_radio_action_get_group" result
    result' <- unpackGSList result
    result'' <- mapM (newObject RadioAction) result'
    touchManagedPtr _obj
    return result''

-- method RadioAction::join_group
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RadioAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "group_source", argType = TInterface "Gtk" "RadioAction", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RadioAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "group_source", argType = TInterface "Gtk" "RadioAction", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_radio_action_join_group" gtk_radio_action_join_group :: 
    Ptr RadioAction ->                      -- _obj : TInterface "Gtk" "RadioAction"
    Ptr RadioAction ->                      -- group_source : TInterface "Gtk" "RadioAction"
    IO ()

{-# DEPRECATED radioActionJoinGroup ["(Since version 3.10)"]#-}
radioActionJoinGroup ::
    (MonadIO m, RadioActionK a, RadioActionK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- group_source
    m ()
radioActionJoinGroup _obj group_source = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeGroup_source <- case group_source of
        Nothing -> return nullPtr
        Just jGroup_source -> do
            let jGroup_source' = unsafeManagedPtrCastPtr jGroup_source
            return jGroup_source'
    gtk_radio_action_join_group _obj' maybeGroup_source
    touchManagedPtr _obj
    whenJust group_source touchManagedPtr
    return ()

-- method RadioAction::set_current_value
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RadioAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "current_value", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RadioAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "current_value", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_radio_action_set_current_value" gtk_radio_action_set_current_value :: 
    Ptr RadioAction ->                      -- _obj : TInterface "Gtk" "RadioAction"
    Int32 ->                                -- current_value : TBasicType TInt32
    IO ()

{-# DEPRECATED radioActionSetCurrentValue ["(Since version 3.10)"]#-}
radioActionSetCurrentValue ::
    (MonadIO m, RadioActionK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- current_value
    m ()
radioActionSetCurrentValue _obj current_value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_radio_action_set_current_value _obj' current_value
    touchManagedPtr _obj
    return ()

-- method RadioAction::set_group
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RadioAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "group", argType = TGSList (TInterface "Gtk" "RadioAction"), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RadioAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "group", argType = TGSList (TInterface "Gtk" "RadioAction"), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_radio_action_set_group" gtk_radio_action_set_group :: 
    Ptr RadioAction ->                      -- _obj : TInterface "Gtk" "RadioAction"
    Ptr (GSList (Ptr RadioAction)) ->       -- group : TGSList (TInterface "Gtk" "RadioAction")
    IO ()

{-# DEPRECATED radioActionSetGroup ["(Since version 3.10)"]#-}
radioActionSetGroup ::
    (MonadIO m, RadioActionK a, RadioActionK b) =>
    a ->                                    -- _obj
    [b] ->                                  -- group
    m ()
radioActionSetGroup _obj group = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let group' = map unsafeManagedPtrCastPtr group
    group'' <- packGSList group'
    gtk_radio_action_set_group _obj' group''
    touchManagedPtr _obj
    mapM_ touchManagedPtr group
    g_slist_free group''
    return ()