{- |
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.CheckMenuItem
    ( 

-- * Exported types
    CheckMenuItem(..)                       ,
    CheckMenuItemK                          ,
    toCheckMenuItem                         ,
    noCheckMenuItem                         ,


 -- * Methods
-- ** checkMenuItemGetActive
    checkMenuItemGetActive                  ,


-- ** checkMenuItemGetDrawAsRadio
    checkMenuItemGetDrawAsRadio             ,


-- ** checkMenuItemGetInconsistent
    checkMenuItemGetInconsistent            ,


-- ** checkMenuItemNew
    checkMenuItemNew                        ,


-- ** checkMenuItemNewWithLabel
    checkMenuItemNewWithLabel               ,


-- ** checkMenuItemNewWithMnemonic
    checkMenuItemNewWithMnemonic            ,


-- ** checkMenuItemSetActive
    checkMenuItemSetActive                  ,


-- ** checkMenuItemSetDrawAsRadio
    checkMenuItemSetDrawAsRadio             ,


-- ** checkMenuItemSetInconsistent
    checkMenuItemSetInconsistent            ,


-- ** checkMenuItemToggled
    checkMenuItemToggled                    ,




 -- * Properties
-- ** Active
    CheckMenuItemActivePropertyInfo         ,
    constructCheckMenuItemActive            ,
    getCheckMenuItemActive                  ,
    setCheckMenuItemActive                  ,


-- ** DrawAsRadio
    CheckMenuItemDrawAsRadioPropertyInfo    ,
    constructCheckMenuItemDrawAsRadio       ,
    getCheckMenuItemDrawAsRadio             ,
    setCheckMenuItemDrawAsRadio             ,


-- ** Inconsistent
    CheckMenuItemInconsistentPropertyInfo   ,
    constructCheckMenuItemInconsistent      ,
    getCheckMenuItemInconsistent            ,
    setCheckMenuItemInconsistent            ,




 -- * Signals
-- ** Toggled
    CheckMenuItemToggledCallback            ,
    CheckMenuItemToggledCallbackC           ,
    CheckMenuItemToggledSignalInfo          ,
    afterCheckMenuItemToggled               ,
    checkMenuItemToggledCallbackWrapper     ,
    checkMenuItemToggledClosure             ,
    mkCheckMenuItemToggledCallback          ,
    noCheckMenuItemToggledCallback          ,
    onCheckMenuItemToggled                  ,




    ) 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.Atk as Atk
import qualified GI.GObject as GObject

newtype CheckMenuItem = CheckMenuItem (ForeignPtr CheckMenuItem)
foreign import ccall "gtk_check_menu_item_get_type"
    c_gtk_check_menu_item_get_type :: IO GType

type instance ParentTypes CheckMenuItem = CheckMenuItemParentTypes
type CheckMenuItemParentTypes = '[MenuItem, Bin, Container, Widget, GObject.Object, Atk.ImplementorIface, Actionable, Activatable, Buildable]

instance GObject CheckMenuItem where
    gobjectIsInitiallyUnowned _ = True
    gobjectType _ = c_gtk_check_menu_item_get_type
    

class GObject o => CheckMenuItemK o
instance (GObject o, IsDescendantOf CheckMenuItem o) => CheckMenuItemK o

toCheckMenuItem :: CheckMenuItemK o => o -> IO CheckMenuItem
toCheckMenuItem = unsafeCastTo CheckMenuItem

noCheckMenuItem :: Maybe CheckMenuItem
noCheckMenuItem = Nothing

-- signal CheckMenuItem::toggled
type CheckMenuItemToggledCallback =
    IO ()

noCheckMenuItemToggledCallback :: Maybe CheckMenuItemToggledCallback
noCheckMenuItemToggledCallback = Nothing

type CheckMenuItemToggledCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkCheckMenuItemToggledCallback :: CheckMenuItemToggledCallbackC -> IO (FunPtr CheckMenuItemToggledCallbackC)

checkMenuItemToggledClosure :: CheckMenuItemToggledCallback -> IO Closure
checkMenuItemToggledClosure cb = newCClosure =<< mkCheckMenuItemToggledCallback wrapped
    where wrapped = checkMenuItemToggledCallbackWrapper cb

checkMenuItemToggledCallbackWrapper ::
    CheckMenuItemToggledCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
checkMenuItemToggledCallbackWrapper _cb _ _ = do
    _cb 

onCheckMenuItemToggled :: (GObject a, MonadIO m) => a -> CheckMenuItemToggledCallback -> m SignalHandlerId
onCheckMenuItemToggled obj cb = liftIO $ connectCheckMenuItemToggled obj cb SignalConnectBefore
afterCheckMenuItemToggled :: (GObject a, MonadIO m) => a -> CheckMenuItemToggledCallback -> m SignalHandlerId
afterCheckMenuItemToggled obj cb = connectCheckMenuItemToggled obj cb SignalConnectAfter

connectCheckMenuItemToggled :: (GObject a, MonadIO m) =>
                               a -> CheckMenuItemToggledCallback -> SignalConnectMode -> m SignalHandlerId
connectCheckMenuItemToggled obj cb after = liftIO $ do
    cb' <- mkCheckMenuItemToggledCallback (checkMenuItemToggledCallbackWrapper cb)
    connectSignalFunPtr obj "toggled" cb' after

-- VVV Prop "active"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getCheckMenuItemActive :: (MonadIO m, CheckMenuItemK o) => o -> m Bool
getCheckMenuItemActive obj = liftIO $ getObjectPropertyBool obj "active"

setCheckMenuItemActive :: (MonadIO m, CheckMenuItemK o) => o -> Bool -> m ()
setCheckMenuItemActive obj val = liftIO $ setObjectPropertyBool obj "active" val

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

data CheckMenuItemActivePropertyInfo
instance AttrInfo CheckMenuItemActivePropertyInfo where
    type AttrAllowedOps CheckMenuItemActivePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint CheckMenuItemActivePropertyInfo = (~) Bool
    type AttrBaseTypeConstraint CheckMenuItemActivePropertyInfo = CheckMenuItemK
    type AttrGetType CheckMenuItemActivePropertyInfo = Bool
    type AttrLabel CheckMenuItemActivePropertyInfo = "CheckMenuItem::active"
    attrGet _ = getCheckMenuItemActive
    attrSet _ = setCheckMenuItemActive
    attrConstruct _ = constructCheckMenuItemActive

-- VVV Prop "draw-as-radio"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getCheckMenuItemDrawAsRadio :: (MonadIO m, CheckMenuItemK o) => o -> m Bool
getCheckMenuItemDrawAsRadio obj = liftIO $ getObjectPropertyBool obj "draw-as-radio"

setCheckMenuItemDrawAsRadio :: (MonadIO m, CheckMenuItemK o) => o -> Bool -> m ()
setCheckMenuItemDrawAsRadio obj val = liftIO $ setObjectPropertyBool obj "draw-as-radio" val

constructCheckMenuItemDrawAsRadio :: Bool -> IO ([Char], GValue)
constructCheckMenuItemDrawAsRadio val = constructObjectPropertyBool "draw-as-radio" val

data CheckMenuItemDrawAsRadioPropertyInfo
instance AttrInfo CheckMenuItemDrawAsRadioPropertyInfo where
    type AttrAllowedOps CheckMenuItemDrawAsRadioPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint CheckMenuItemDrawAsRadioPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint CheckMenuItemDrawAsRadioPropertyInfo = CheckMenuItemK
    type AttrGetType CheckMenuItemDrawAsRadioPropertyInfo = Bool
    type AttrLabel CheckMenuItemDrawAsRadioPropertyInfo = "CheckMenuItem::draw-as-radio"
    attrGet _ = getCheckMenuItemDrawAsRadio
    attrSet _ = setCheckMenuItemDrawAsRadio
    attrConstruct _ = constructCheckMenuItemDrawAsRadio

-- VVV Prop "inconsistent"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getCheckMenuItemInconsistent :: (MonadIO m, CheckMenuItemK o) => o -> m Bool
getCheckMenuItemInconsistent obj = liftIO $ getObjectPropertyBool obj "inconsistent"

setCheckMenuItemInconsistent :: (MonadIO m, CheckMenuItemK o) => o -> Bool -> m ()
setCheckMenuItemInconsistent obj val = liftIO $ setObjectPropertyBool obj "inconsistent" val

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

data CheckMenuItemInconsistentPropertyInfo
instance AttrInfo CheckMenuItemInconsistentPropertyInfo where
    type AttrAllowedOps CheckMenuItemInconsistentPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint CheckMenuItemInconsistentPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint CheckMenuItemInconsistentPropertyInfo = CheckMenuItemK
    type AttrGetType CheckMenuItemInconsistentPropertyInfo = Bool
    type AttrLabel CheckMenuItemInconsistentPropertyInfo = "CheckMenuItem::inconsistent"
    attrGet _ = getCheckMenuItemInconsistent
    attrSet _ = setCheckMenuItemInconsistent
    attrConstruct _ = constructCheckMenuItemInconsistent

type instance AttributeList CheckMenuItem = CheckMenuItemAttributeList
type CheckMenuItemAttributeList = ('[ '("accel-path", MenuItemAccelPathPropertyInfo), '("action-name", ActionableActionNamePropertyInfo), '("action-target", ActionableActionTargetPropertyInfo), '("active", CheckMenuItemActivePropertyInfo), '("app-paintable", WidgetAppPaintablePropertyInfo), '("border-width", ContainerBorderWidthPropertyInfo), '("can-default", WidgetCanDefaultPropertyInfo), '("can-focus", WidgetCanFocusPropertyInfo), '("child", ContainerChildPropertyInfo), '("composite-child", WidgetCompositeChildPropertyInfo), '("double-buffered", WidgetDoubleBufferedPropertyInfo), '("draw-as-radio", CheckMenuItemDrawAsRadioPropertyInfo), '("events", WidgetEventsPropertyInfo), '("expand", WidgetExpandPropertyInfo), '("halign", WidgetHalignPropertyInfo), '("has-default", WidgetHasDefaultPropertyInfo), '("has-focus", WidgetHasFocusPropertyInfo), '("has-tooltip", WidgetHasTooltipPropertyInfo), '("height-request", WidgetHeightRequestPropertyInfo), '("hexpand", WidgetHexpandPropertyInfo), '("hexpand-set", WidgetHexpandSetPropertyInfo), '("inconsistent", CheckMenuItemInconsistentPropertyInfo), '("is-focus", WidgetIsFocusPropertyInfo), '("label", MenuItemLabelPropertyInfo), '("margin", WidgetMarginPropertyInfo), '("margin-bottom", WidgetMarginBottomPropertyInfo), '("margin-end", WidgetMarginEndPropertyInfo), '("margin-left", WidgetMarginLeftPropertyInfo), '("margin-right", WidgetMarginRightPropertyInfo), '("margin-start", WidgetMarginStartPropertyInfo), '("margin-top", WidgetMarginTopPropertyInfo), '("name", WidgetNamePropertyInfo), '("no-show-all", WidgetNoShowAllPropertyInfo), '("opacity", WidgetOpacityPropertyInfo), '("parent", WidgetParentPropertyInfo), '("receives-default", WidgetReceivesDefaultPropertyInfo), '("related-action", ActivatableRelatedActionPropertyInfo), '("resize-mode", ContainerResizeModePropertyInfo), '("right-justified", MenuItemRightJustifiedPropertyInfo), '("scale-factor", WidgetScaleFactorPropertyInfo), '("sensitive", WidgetSensitivePropertyInfo), '("style", WidgetStylePropertyInfo), '("submenu", MenuItemSubmenuPropertyInfo), '("tooltip-markup", WidgetTooltipMarkupPropertyInfo), '("tooltip-text", WidgetTooltipTextPropertyInfo), '("use-action-appearance", ActivatableUseActionAppearancePropertyInfo), '("use-underline", MenuItemUseUnderlinePropertyInfo), '("valign", WidgetValignPropertyInfo), '("vexpand", WidgetVexpandPropertyInfo), '("vexpand-set", WidgetVexpandSetPropertyInfo), '("visible", WidgetVisiblePropertyInfo), '("width-request", WidgetWidthRequestPropertyInfo), '("window", WidgetWindowPropertyInfo)] :: [(Symbol, *)])

data CheckMenuItemToggledSignalInfo
instance SignalInfo CheckMenuItemToggledSignalInfo where
    type HaskellCallbackType CheckMenuItemToggledSignalInfo = CheckMenuItemToggledCallback
    connectSignal _ = connectCheckMenuItemToggled

type instance SignalList CheckMenuItem = CheckMenuItemSignalList
type CheckMenuItemSignalList = ('[ '("accel-closures-changed", WidgetAccelClosuresChangedSignalInfo), '("activate", MenuItemActivateSignalInfo), '("activate-item", MenuItemActivateItemSignalInfo), '("add", ContainerAddSignalInfo), '("button-press-event", WidgetButtonPressEventSignalInfo), '("button-release-event", WidgetButtonReleaseEventSignalInfo), '("can-activate-accel", WidgetCanActivateAccelSignalInfo), '("check-resize", ContainerCheckResizeSignalInfo), '("child-notify", WidgetChildNotifySignalInfo), '("composited-changed", WidgetCompositedChangedSignalInfo), '("configure-event", WidgetConfigureEventSignalInfo), '("damage-event", WidgetDamageEventSignalInfo), '("delete-event", WidgetDeleteEventSignalInfo), '("deselect", MenuItemDeselectSignalInfo), '("destroy", WidgetDestroySignalInfo), '("destroy-event", WidgetDestroyEventSignalInfo), '("direction-changed", WidgetDirectionChangedSignalInfo), '("drag-begin", WidgetDragBeginSignalInfo), '("drag-data-delete", WidgetDragDataDeleteSignalInfo), '("drag-data-get", WidgetDragDataGetSignalInfo), '("drag-data-received", WidgetDragDataReceivedSignalInfo), '("drag-drop", WidgetDragDropSignalInfo), '("drag-end", WidgetDragEndSignalInfo), '("drag-failed", WidgetDragFailedSignalInfo), '("drag-leave", WidgetDragLeaveSignalInfo), '("drag-motion", WidgetDragMotionSignalInfo), '("draw", WidgetDrawSignalInfo), '("enter-notify-event", WidgetEnterNotifyEventSignalInfo), '("event", WidgetEventSignalInfo), '("event-after", WidgetEventAfterSignalInfo), '("focus", WidgetFocusSignalInfo), '("focus-in-event", WidgetFocusInEventSignalInfo), '("focus-out-event", WidgetFocusOutEventSignalInfo), '("grab-broken-event", WidgetGrabBrokenEventSignalInfo), '("grab-focus", WidgetGrabFocusSignalInfo), '("grab-notify", WidgetGrabNotifySignalInfo), '("hide", WidgetHideSignalInfo), '("hierarchy-changed", WidgetHierarchyChangedSignalInfo), '("key-press-event", WidgetKeyPressEventSignalInfo), '("key-release-event", WidgetKeyReleaseEventSignalInfo), '("keynav-failed", WidgetKeynavFailedSignalInfo), '("leave-notify-event", WidgetLeaveNotifyEventSignalInfo), '("map", WidgetMapSignalInfo), '("map-event", WidgetMapEventSignalInfo), '("mnemonic-activate", WidgetMnemonicActivateSignalInfo), '("motion-notify-event", WidgetMotionNotifyEventSignalInfo), '("move-focus", WidgetMoveFocusSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("parent-set", WidgetParentSetSignalInfo), '("popup-menu", WidgetPopupMenuSignalInfo), '("property-notify-event", WidgetPropertyNotifyEventSignalInfo), '("proximity-in-event", WidgetProximityInEventSignalInfo), '("proximity-out-event", WidgetProximityOutEventSignalInfo), '("query-tooltip", WidgetQueryTooltipSignalInfo), '("realize", WidgetRealizeSignalInfo), '("remove", ContainerRemoveSignalInfo), '("screen-changed", WidgetScreenChangedSignalInfo), '("scroll-event", WidgetScrollEventSignalInfo), '("select", MenuItemSelectSignalInfo), '("selection-clear-event", WidgetSelectionClearEventSignalInfo), '("selection-get", WidgetSelectionGetSignalInfo), '("selection-notify-event", WidgetSelectionNotifyEventSignalInfo), '("selection-received", WidgetSelectionReceivedSignalInfo), '("selection-request-event", WidgetSelectionRequestEventSignalInfo), '("set-focus-child", ContainerSetFocusChildSignalInfo), '("show", WidgetShowSignalInfo), '("show-help", WidgetShowHelpSignalInfo), '("size-allocate", WidgetSizeAllocateSignalInfo), '("state-changed", WidgetStateChangedSignalInfo), '("state-flags-changed", WidgetStateFlagsChangedSignalInfo), '("style-set", WidgetStyleSetSignalInfo), '("style-updated", WidgetStyleUpdatedSignalInfo), '("toggle-size-allocate", MenuItemToggleSizeAllocateSignalInfo), '("toggle-size-request", MenuItemToggleSizeRequestSignalInfo), '("toggled", CheckMenuItemToggledSignalInfo), '("touch-event", WidgetTouchEventSignalInfo), '("unmap", WidgetUnmapSignalInfo), '("unmap-event", WidgetUnmapEventSignalInfo), '("unrealize", WidgetUnrealizeSignalInfo), '("visibility-notify-event", WidgetVisibilityNotifyEventSignalInfo), '("window-state-event", WidgetWindowStateEventSignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method CheckMenuItem::new
-- method type : Constructor
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "Gtk" "CheckMenuItem"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_check_menu_item_new" gtk_check_menu_item_new :: 
    IO (Ptr CheckMenuItem)


checkMenuItemNew ::
    (MonadIO m) =>
    m CheckMenuItem
checkMenuItemNew  = liftIO $ do
    result <- gtk_check_menu_item_new
    checkUnexpectedReturnNULL "gtk_check_menu_item_new" result
    result' <- (newObject CheckMenuItem) result
    return result'

-- method CheckMenuItem::new_with_label
-- method type : Constructor
-- Args : [Arg {argName = "label", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "label", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "CheckMenuItem"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_check_menu_item_new_with_label" gtk_check_menu_item_new_with_label :: 
    CString ->                              -- label : TBasicType TUTF8
    IO (Ptr CheckMenuItem)


checkMenuItemNewWithLabel ::
    (MonadIO m) =>
    T.Text ->                               -- label
    m CheckMenuItem
checkMenuItemNewWithLabel label = liftIO $ do
    label' <- textToCString label
    result <- gtk_check_menu_item_new_with_label label'
    checkUnexpectedReturnNULL "gtk_check_menu_item_new_with_label" result
    result' <- (newObject CheckMenuItem) result
    freeMem label'
    return result'

-- method CheckMenuItem::new_with_mnemonic
-- method type : Constructor
-- Args : [Arg {argName = "label", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "label", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "CheckMenuItem"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_check_menu_item_new_with_mnemonic" gtk_check_menu_item_new_with_mnemonic :: 
    CString ->                              -- label : TBasicType TUTF8
    IO (Ptr CheckMenuItem)


checkMenuItemNewWithMnemonic ::
    (MonadIO m) =>
    T.Text ->                               -- label
    m CheckMenuItem
checkMenuItemNewWithMnemonic label = liftIO $ do
    label' <- textToCString label
    result <- gtk_check_menu_item_new_with_mnemonic label'
    checkUnexpectedReturnNULL "gtk_check_menu_item_new_with_mnemonic" result
    result' <- (newObject CheckMenuItem) result
    freeMem label'
    return result'

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

foreign import ccall "gtk_check_menu_item_get_active" gtk_check_menu_item_get_active :: 
    Ptr CheckMenuItem ->                    -- _obj : TInterface "Gtk" "CheckMenuItem"
    IO CInt


checkMenuItemGetActive ::
    (MonadIO m, CheckMenuItemK a) =>
    a ->                                    -- _obj
    m Bool
checkMenuItemGetActive _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_check_menu_item_get_active _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_check_menu_item_get_draw_as_radio" gtk_check_menu_item_get_draw_as_radio :: 
    Ptr CheckMenuItem ->                    -- _obj : TInterface "Gtk" "CheckMenuItem"
    IO CInt


checkMenuItemGetDrawAsRadio ::
    (MonadIO m, CheckMenuItemK a) =>
    a ->                                    -- _obj
    m Bool
checkMenuItemGetDrawAsRadio _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_check_menu_item_get_draw_as_radio _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_check_menu_item_get_inconsistent" gtk_check_menu_item_get_inconsistent :: 
    Ptr CheckMenuItem ->                    -- _obj : TInterface "Gtk" "CheckMenuItem"
    IO CInt


checkMenuItemGetInconsistent ::
    (MonadIO m, CheckMenuItemK a) =>
    a ->                                    -- _obj
    m Bool
checkMenuItemGetInconsistent _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_check_menu_item_get_inconsistent _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method CheckMenuItem::set_active
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CheckMenuItem", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "is_active", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CheckMenuItem", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "is_active", 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 "gtk_check_menu_item_set_active" gtk_check_menu_item_set_active :: 
    Ptr CheckMenuItem ->                    -- _obj : TInterface "Gtk" "CheckMenuItem"
    CInt ->                                 -- is_active : TBasicType TBoolean
    IO ()


checkMenuItemSetActive ::
    (MonadIO m, CheckMenuItemK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- is_active
    m ()
checkMenuItemSetActive _obj is_active = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let is_active' = (fromIntegral . fromEnum) is_active
    gtk_check_menu_item_set_active _obj' is_active'
    touchManagedPtr _obj
    return ()

-- method CheckMenuItem::set_draw_as_radio
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CheckMenuItem", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "draw_as_radio", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CheckMenuItem", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "draw_as_radio", 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 "gtk_check_menu_item_set_draw_as_radio" gtk_check_menu_item_set_draw_as_radio :: 
    Ptr CheckMenuItem ->                    -- _obj : TInterface "Gtk" "CheckMenuItem"
    CInt ->                                 -- draw_as_radio : TBasicType TBoolean
    IO ()


checkMenuItemSetDrawAsRadio ::
    (MonadIO m, CheckMenuItemK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- draw_as_radio
    m ()
checkMenuItemSetDrawAsRadio _obj draw_as_radio = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let draw_as_radio' = (fromIntegral . fromEnum) draw_as_radio
    gtk_check_menu_item_set_draw_as_radio _obj' draw_as_radio'
    touchManagedPtr _obj
    return ()

-- method CheckMenuItem::set_inconsistent
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CheckMenuItem", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "setting", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CheckMenuItem", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "setting", 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 "gtk_check_menu_item_set_inconsistent" gtk_check_menu_item_set_inconsistent :: 
    Ptr CheckMenuItem ->                    -- _obj : TInterface "Gtk" "CheckMenuItem"
    CInt ->                                 -- setting : TBasicType TBoolean
    IO ()


checkMenuItemSetInconsistent ::
    (MonadIO m, CheckMenuItemK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- setting
    m ()
checkMenuItemSetInconsistent _obj setting = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let setting' = (fromIntegral . fromEnum) setting
    gtk_check_menu_item_set_inconsistent _obj' setting'
    touchManagedPtr _obj
    return ()

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

foreign import ccall "gtk_check_menu_item_toggled" gtk_check_menu_item_toggled :: 
    Ptr CheckMenuItem ->                    -- _obj : TInterface "Gtk" "CheckMenuItem"
    IO ()


checkMenuItemToggled ::
    (MonadIO m, CheckMenuItemK a) =>
    a ->                                    -- _obj
    m ()
checkMenuItemToggled _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_check_menu_item_toggled _obj'
    touchManagedPtr _obj
    return ()