{- |
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.Gio.Objects.SimpleAction
    ( 

-- * Exported types
    SimpleAction(..)                        ,
    SimpleActionK                           ,
    toSimpleAction                          ,
    noSimpleAction                          ,


 -- * Methods
-- ** simpleActionNew
    simpleActionNew                         ,


-- ** simpleActionNewStateful
    simpleActionNewStateful                 ,


-- ** simpleActionSetEnabled
    simpleActionSetEnabled                  ,


-- ** simpleActionSetState
    simpleActionSetState                    ,


-- ** simpleActionSetStateHint
    simpleActionSetStateHint                ,




 -- * Properties
-- ** Enabled
    SimpleActionEnabledPropertyInfo         ,
    constructSimpleActionEnabled            ,
    getSimpleActionEnabled                  ,
    setSimpleActionEnabled                  ,


-- ** Name
    SimpleActionNamePropertyInfo            ,
    constructSimpleActionName               ,
    getSimpleActionName                     ,


-- ** ParameterType
    SimpleActionParameterTypePropertyInfo   ,
    constructSimpleActionParameterType      ,
    getSimpleActionParameterType            ,


-- ** State
    SimpleActionStatePropertyInfo           ,
    constructSimpleActionState              ,
    getSimpleActionState                    ,
    setSimpleActionState                    ,


-- ** StateType
    SimpleActionStateTypePropertyInfo       ,
    getSimpleActionStateType                ,




 -- * Signals
-- ** Activate
    SimpleActionActivateCallback            ,
    SimpleActionActivateCallbackC           ,
    SimpleActionActivateSignalInfo          ,
    afterSimpleActionActivate               ,
    mkSimpleActionActivateCallback          ,
    noSimpleActionActivateCallback          ,
    onSimpleActionActivate                  ,
    simpleActionActivateCallbackWrapper     ,
    simpleActionActivateClosure             ,


-- ** ChangeState
    SimpleActionChangeStateCallback         ,
    SimpleActionChangeStateCallbackC        ,
    SimpleActionChangeStateSignalInfo       ,
    afterSimpleActionChangeState            ,
    mkSimpleActionChangeStateCallback       ,
    noSimpleActionChangeStateCallback       ,
    onSimpleActionChangeState               ,
    simpleActionChangeStateCallbackWrapper  ,
    simpleActionChangeStateClosure          ,




    ) 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.Gio.Types
import GI.Gio.Callbacks
import qualified GI.GLib as GLib
import qualified GI.GObject as GObject

newtype SimpleAction = SimpleAction (ForeignPtr SimpleAction)
foreign import ccall "g_simple_action_get_type"
    c_g_simple_action_get_type :: IO GType

type instance ParentTypes SimpleAction = SimpleActionParentTypes
type SimpleActionParentTypes = '[GObject.Object, Action]

instance GObject SimpleAction where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_g_simple_action_get_type
    

class GObject o => SimpleActionK o
instance (GObject o, IsDescendantOf SimpleAction o) => SimpleActionK o

toSimpleAction :: SimpleActionK o => o -> IO SimpleAction
toSimpleAction = unsafeCastTo SimpleAction

noSimpleAction :: Maybe SimpleAction
noSimpleAction = Nothing

-- signal SimpleAction::activate
type SimpleActionActivateCallback =
    Maybe GVariant ->
    IO ()

noSimpleActionActivateCallback :: Maybe SimpleActionActivateCallback
noSimpleActionActivateCallback = Nothing

type SimpleActionActivateCallbackC =
    Ptr () ->                               -- object
    Ptr GVariant ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkSimpleActionActivateCallback :: SimpleActionActivateCallbackC -> IO (FunPtr SimpleActionActivateCallbackC)

simpleActionActivateClosure :: SimpleActionActivateCallback -> IO Closure
simpleActionActivateClosure cb = newCClosure =<< mkSimpleActionActivateCallback wrapped
    where wrapped = simpleActionActivateCallbackWrapper cb

simpleActionActivateCallbackWrapper ::
    SimpleActionActivateCallback ->
    Ptr () ->
    Ptr GVariant ->
    Ptr () ->
    IO ()
simpleActionActivateCallbackWrapper _cb _ parameter _ = do
    maybeParameter <-
        if parameter == nullPtr
        then return Nothing
        else do
            parameter' <- newGVariantFromPtr parameter
            return $ Just parameter'
    _cb  maybeParameter

onSimpleActionActivate :: (GObject a, MonadIO m) => a -> SimpleActionActivateCallback -> m SignalHandlerId
onSimpleActionActivate obj cb = liftIO $ connectSimpleActionActivate obj cb SignalConnectBefore
afterSimpleActionActivate :: (GObject a, MonadIO m) => a -> SimpleActionActivateCallback -> m SignalHandlerId
afterSimpleActionActivate obj cb = connectSimpleActionActivate obj cb SignalConnectAfter

connectSimpleActionActivate :: (GObject a, MonadIO m) =>
                               a -> SimpleActionActivateCallback -> SignalConnectMode -> m SignalHandlerId
connectSimpleActionActivate obj cb after = liftIO $ do
    cb' <- mkSimpleActionActivateCallback (simpleActionActivateCallbackWrapper cb)
    connectSignalFunPtr obj "activate" cb' after

-- signal SimpleAction::change-state
type SimpleActionChangeStateCallback =
    Maybe GVariant ->
    IO ()

noSimpleActionChangeStateCallback :: Maybe SimpleActionChangeStateCallback
noSimpleActionChangeStateCallback = Nothing

type SimpleActionChangeStateCallbackC =
    Ptr () ->                               -- object
    Ptr GVariant ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkSimpleActionChangeStateCallback :: SimpleActionChangeStateCallbackC -> IO (FunPtr SimpleActionChangeStateCallbackC)

simpleActionChangeStateClosure :: SimpleActionChangeStateCallback -> IO Closure
simpleActionChangeStateClosure cb = newCClosure =<< mkSimpleActionChangeStateCallback wrapped
    where wrapped = simpleActionChangeStateCallbackWrapper cb

simpleActionChangeStateCallbackWrapper ::
    SimpleActionChangeStateCallback ->
    Ptr () ->
    Ptr GVariant ->
    Ptr () ->
    IO ()
simpleActionChangeStateCallbackWrapper _cb _ value _ = do
    maybeValue <-
        if value == nullPtr
        then return Nothing
        else do
            value' <- newGVariantFromPtr value
            return $ Just value'
    _cb  maybeValue

onSimpleActionChangeState :: (GObject a, MonadIO m) => a -> SimpleActionChangeStateCallback -> m SignalHandlerId
onSimpleActionChangeState obj cb = liftIO $ connectSimpleActionChangeState obj cb SignalConnectBefore
afterSimpleActionChangeState :: (GObject a, MonadIO m) => a -> SimpleActionChangeStateCallback -> m SignalHandlerId
afterSimpleActionChangeState obj cb = connectSimpleActionChangeState obj cb SignalConnectAfter

connectSimpleActionChangeState :: (GObject a, MonadIO m) =>
                                  a -> SimpleActionChangeStateCallback -> SignalConnectMode -> m SignalHandlerId
connectSimpleActionChangeState obj cb after = liftIO $ do
    cb' <- mkSimpleActionChangeStateCallback (simpleActionChangeStateCallbackWrapper cb)
    connectSignalFunPtr obj "change-state" cb' after

--- XXX Duplicated object with different types:
  --- Name {namespace = "Gio", name = "SimpleAction"} -> Property {propName = "enabled", propType = TBasicType TBoolean, propFlags = [PropertyReadable,PropertyWritable], propTransfer = TransferNothing, propDeprecated = Nothing}
  --- Name {namespace = "Gio", name = "Action"} -> Property {propName = "enabled", propType = TBasicType TBoolean, propFlags = [PropertyReadable], propTransfer = TransferNothing, propDeprecated = Nothing}
--- XXX Duplicated object with different types:
  --- Name {namespace = "Gio", name = "SimpleAction"} -> Property {propName = "name", propType = TBasicType TUTF8, propFlags = [PropertyReadable,PropertyWritable,PropertyConstructOnly], propTransfer = TransferNothing, propDeprecated = Nothing}
  --- Name {namespace = "Gio", name = "Action"} -> Property {propName = "name", propType = TBasicType TUTF8, propFlags = [PropertyReadable], propTransfer = TransferNothing, propDeprecated = Nothing}
--- XXX Duplicated object with different types:
  --- Name {namespace = "Gio", name = "SimpleAction"} -> Property {propName = "parameter-type", propType = TInterface "GLib" "VariantType", propFlags = [PropertyReadable,PropertyWritable,PropertyConstructOnly], propTransfer = TransferNothing, propDeprecated = Nothing}
  --- Name {namespace = "Gio", name = "Action"} -> Property {propName = "parameter-type", propType = TInterface "GLib" "VariantType", propFlags = [PropertyReadable], propTransfer = TransferNothing, propDeprecated = Nothing}
--- XXX Duplicated object with different types:
  --- Name {namespace = "Gio", name = "SimpleAction"} -> Property {propName = "state", propType = TVariant, propFlags = [PropertyReadable,PropertyWritable,PropertyConstruct], propTransfer = TransferNothing, propDeprecated = Nothing}
  --- Name {namespace = "Gio", name = "Action"} -> Property {propName = "state", propType = TVariant, propFlags = [PropertyReadable], propTransfer = TransferNothing, propDeprecated = Nothing}
-- VVV Prop "enabled"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getSimpleActionEnabled :: (MonadIO m, SimpleActionK o) => o -> m Bool
getSimpleActionEnabled obj = liftIO $ getObjectPropertyBool obj "enabled"

setSimpleActionEnabled :: (MonadIO m, SimpleActionK o) => o -> Bool -> m ()
setSimpleActionEnabled obj val = liftIO $ setObjectPropertyBool obj "enabled" val

constructSimpleActionEnabled :: Bool -> IO ([Char], GValue)
constructSimpleActionEnabled val = constructObjectPropertyBool "enabled" val

data SimpleActionEnabledPropertyInfo
instance AttrInfo SimpleActionEnabledPropertyInfo where
    type AttrAllowedOps SimpleActionEnabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint SimpleActionEnabledPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint SimpleActionEnabledPropertyInfo = SimpleActionK
    type AttrGetType SimpleActionEnabledPropertyInfo = Bool
    type AttrLabel SimpleActionEnabledPropertyInfo = "SimpleAction::enabled"
    attrGet _ = getSimpleActionEnabled
    attrSet _ = setSimpleActionEnabled
    attrConstruct _ = constructSimpleActionEnabled

-- VVV Prop "name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]

getSimpleActionName :: (MonadIO m, SimpleActionK o) => o -> m T.Text
getSimpleActionName obj = liftIO $ getObjectPropertyString obj "name"

constructSimpleActionName :: T.Text -> IO ([Char], GValue)
constructSimpleActionName val = constructObjectPropertyString "name" val

data SimpleActionNamePropertyInfo
instance AttrInfo SimpleActionNamePropertyInfo where
    type AttrAllowedOps SimpleActionNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint SimpleActionNamePropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint SimpleActionNamePropertyInfo = SimpleActionK
    type AttrGetType SimpleActionNamePropertyInfo = T.Text
    type AttrLabel SimpleActionNamePropertyInfo = "SimpleAction::name"
    attrGet _ = getSimpleActionName
    attrSet _ = undefined
    attrConstruct _ = constructSimpleActionName

-- VVV Prop "parameter-type"
   -- Type: TInterface "GLib" "VariantType"
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]

getSimpleActionParameterType :: (MonadIO m, SimpleActionK o) => o -> m GLib.VariantType
getSimpleActionParameterType obj = liftIO $ getObjectPropertyBoxed obj "parameter-type" GLib.VariantType

constructSimpleActionParameterType :: GLib.VariantType -> IO ([Char], GValue)
constructSimpleActionParameterType val = constructObjectPropertyBoxed "parameter-type" val

data SimpleActionParameterTypePropertyInfo
instance AttrInfo SimpleActionParameterTypePropertyInfo where
    type AttrAllowedOps SimpleActionParameterTypePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint SimpleActionParameterTypePropertyInfo = (~) GLib.VariantType
    type AttrBaseTypeConstraint SimpleActionParameterTypePropertyInfo = SimpleActionK
    type AttrGetType SimpleActionParameterTypePropertyInfo = GLib.VariantType
    type AttrLabel SimpleActionParameterTypePropertyInfo = "SimpleAction::parameter-type"
    attrGet _ = getSimpleActionParameterType
    attrSet _ = undefined
    attrConstruct _ = constructSimpleActionParameterType

-- VVV Prop "state"
   -- Type: TVariant
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]

getSimpleActionState :: (MonadIO m, SimpleActionK o) => o -> m GVariant
getSimpleActionState obj = liftIO $ getObjectPropertyVariant obj "state"

setSimpleActionState :: (MonadIO m, SimpleActionK o) => o -> GVariant -> m ()
setSimpleActionState obj val = liftIO $ setObjectPropertyVariant obj "state" val

constructSimpleActionState :: GVariant -> IO ([Char], GValue)
constructSimpleActionState val = constructObjectPropertyVariant "state" val

data SimpleActionStatePropertyInfo
instance AttrInfo SimpleActionStatePropertyInfo where
    type AttrAllowedOps SimpleActionStatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint SimpleActionStatePropertyInfo = (~) GVariant
    type AttrBaseTypeConstraint SimpleActionStatePropertyInfo = SimpleActionK
    type AttrGetType SimpleActionStatePropertyInfo = GVariant
    type AttrLabel SimpleActionStatePropertyInfo = "SimpleAction::state"
    attrGet _ = getSimpleActionState
    attrSet _ = setSimpleActionState
    attrConstruct _ = constructSimpleActionState

-- VVV Prop "state-type"
   -- Type: TInterface "GLib" "VariantType"
   -- Flags: [PropertyReadable]

getSimpleActionStateType :: (MonadIO m, SimpleActionK o) => o -> m GLib.VariantType
getSimpleActionStateType obj = liftIO $ getObjectPropertyBoxed obj "state-type" GLib.VariantType

data SimpleActionStateTypePropertyInfo
instance AttrInfo SimpleActionStateTypePropertyInfo where
    type AttrAllowedOps SimpleActionStateTypePropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint SimpleActionStateTypePropertyInfo = (~) ()
    type AttrBaseTypeConstraint SimpleActionStateTypePropertyInfo = SimpleActionK
    type AttrGetType SimpleActionStateTypePropertyInfo = GLib.VariantType
    type AttrLabel SimpleActionStateTypePropertyInfo = "SimpleAction::state-type"
    attrGet _ = getSimpleActionStateType
    attrSet _ = undefined
    attrConstruct _ = undefined

type instance AttributeList SimpleAction = SimpleActionAttributeList
type SimpleActionAttributeList = ('[ '("state-type", SimpleActionStateTypePropertyInfo)] :: [(Symbol, *)])

data SimpleActionActivateSignalInfo
instance SignalInfo SimpleActionActivateSignalInfo where
    type HaskellCallbackType SimpleActionActivateSignalInfo = SimpleActionActivateCallback
    connectSignal _ = connectSimpleActionActivate

data SimpleActionChangeStateSignalInfo
instance SignalInfo SimpleActionChangeStateSignalInfo where
    type HaskellCallbackType SimpleActionChangeStateSignalInfo = SimpleActionChangeStateCallback
    connectSignal _ = connectSimpleActionChangeState

type instance SignalList SimpleAction = SimpleActionSignalList
type SimpleActionSignalList = ('[ '("activate", SimpleActionActivateSignalInfo), '("change-state", SimpleActionChangeStateSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method SimpleAction::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 = "parameter_type", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = True, 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 = "parameter_type", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "SimpleAction"
-- throws : False
-- Skip return : False

foreign import ccall "g_simple_action_new" g_simple_action_new :: 
    CString ->                              -- name : TBasicType TUTF8
    Ptr GLib.VariantType ->                 -- parameter_type : TInterface "GLib" "VariantType"
    IO (Ptr SimpleAction)


simpleActionNew ::
    (MonadIO m) =>
    T.Text ->                               -- name
    Maybe (GLib.VariantType) ->             -- parameter_type
    m SimpleAction
simpleActionNew name parameter_type = liftIO $ do
    name' <- textToCString name
    maybeParameter_type <- case parameter_type of
        Nothing -> return nullPtr
        Just jParameter_type -> do
            let jParameter_type' = unsafeManagedPtrGetPtr jParameter_type
            return jParameter_type'
    result <- g_simple_action_new name' maybeParameter_type
    checkUnexpectedReturnNULL "g_simple_action_new" result
    result' <- (wrapObject SimpleAction) result
    whenJust parameter_type touchManagedPtr
    freeMem name'
    return result'

-- method SimpleAction::new_stateful
-- method type : Constructor
-- Args : [Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "parameter_type", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "state", argType = TVariant, 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 = "parameter_type", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "state", argType = TVariant, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "SimpleAction"
-- throws : False
-- Skip return : False

foreign import ccall "g_simple_action_new_stateful" g_simple_action_new_stateful :: 
    CString ->                              -- name : TBasicType TUTF8
    Ptr GLib.VariantType ->                 -- parameter_type : TInterface "GLib" "VariantType"
    Ptr GVariant ->                         -- state : TVariant
    IO (Ptr SimpleAction)


simpleActionNewStateful ::
    (MonadIO m) =>
    T.Text ->                               -- name
    Maybe (GLib.VariantType) ->             -- parameter_type
    GVariant ->                             -- state
    m SimpleAction
simpleActionNewStateful name parameter_type state = liftIO $ do
    name' <- textToCString name
    maybeParameter_type <- case parameter_type of
        Nothing -> return nullPtr
        Just jParameter_type -> do
            let jParameter_type' = unsafeManagedPtrGetPtr jParameter_type
            return jParameter_type'
    let state' = unsafeManagedPtrGetPtr state
    result <- g_simple_action_new_stateful name' maybeParameter_type state'
    checkUnexpectedReturnNULL "g_simple_action_new_stateful" result
    result' <- (wrapObject SimpleAction) result
    whenJust parameter_type touchManagedPtr
    freeMem name'
    return result'

-- method SimpleAction::set_enabled
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SimpleAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "enabled", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SimpleAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "enabled", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_simple_action_set_enabled" g_simple_action_set_enabled :: 
    Ptr SimpleAction ->                     -- _obj : TInterface "Gio" "SimpleAction"
    CInt ->                                 -- enabled : TBasicType TBoolean
    IO ()


simpleActionSetEnabled ::
    (MonadIO m, SimpleActionK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- enabled
    m ()
simpleActionSetEnabled _obj enabled = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let enabled' = (fromIntegral . fromEnum) enabled
    g_simple_action_set_enabled _obj' enabled'
    touchManagedPtr _obj
    return ()

-- method SimpleAction::set_state
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "SimpleAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TVariant, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "SimpleAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TVariant, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_simple_action_set_state" g_simple_action_set_state :: 
    Ptr SimpleAction ->                     -- _obj : TInterface "Gio" "SimpleAction"
    Ptr GVariant ->                         -- value : TVariant
    IO ()


simpleActionSetState ::
    (MonadIO m, SimpleActionK a) =>
    a ->                                    -- _obj
    GVariant ->                             -- value
    m ()
simpleActionSetState _obj value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let value' = unsafeManagedPtrGetPtr value
    g_simple_action_set_state _obj' value'
    touchManagedPtr _obj
    return ()

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

foreign import ccall "g_simple_action_set_state_hint" g_simple_action_set_state_hint :: 
    Ptr SimpleAction ->                     -- _obj : TInterface "Gio" "SimpleAction"
    Ptr GVariant ->                         -- state_hint : TVariant
    IO ()


simpleActionSetStateHint ::
    (MonadIO m, SimpleActionK a) =>
    a ->                                    -- _obj
    Maybe (GVariant) ->                     -- state_hint
    m ()
simpleActionSetStateHint _obj state_hint = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeState_hint <- case state_hint of
        Nothing -> return nullPtr
        Just jState_hint -> do
            let jState_hint' = unsafeManagedPtrGetPtr jState_hint
            return jState_hint'
    g_simple_action_set_state_hint _obj' maybeState_hint
    touchManagedPtr _obj
    return ()