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

'GI.Gtk.Structs.ActionEntry.ActionEntry' structs are used with @/gtk_action_group_add_actions()/@ to
construct actions.
-}

module GI.Gtk.Structs.ActionEntry
    ( 

-- * Exported types
    ActionEntry(..)                         ,
    newZeroActionEntry                      ,
    noActionEntry                           ,


 -- * Properties
-- ** accelerator #attr:accelerator#
    actionEntry_accelerator                 ,
    clearActionEntryAccelerator             ,
    getActionEntryAccelerator               ,
    setActionEntryAccelerator               ,


-- ** callback #attr:callback#
    actionEntry_callback                    ,
    clearActionEntryCallback                ,
    getActionEntryCallback                  ,
    setActionEntryCallback                  ,


-- ** label #attr:label#
    actionEntry_label                       ,
    clearActionEntryLabel                   ,
    getActionEntryLabel                     ,
    setActionEntryLabel                     ,


-- ** name #attr:name#
    actionEntry_name                        ,
    clearActionEntryName                    ,
    getActionEntryName                      ,
    setActionEntryName                      ,


-- ** stockId #attr:stockId#
    actionEntry_stockId                     ,
    clearActionEntryStockId                 ,
    getActionEntryStockId                   ,
    setActionEntryStockId                   ,


-- ** tooltip #attr:tooltip#
    actionEntry_tooltip                     ,
    clearActionEntryTooltip                 ,
    getActionEntryTooltip                   ,
    setActionEntryTooltip                   ,




    ) 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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP

import qualified GI.GObject.Callbacks as GObject.Callbacks

newtype ActionEntry = ActionEntry (ManagedPtr ActionEntry)
instance WrappedPtr ActionEntry where
    wrappedPtrCalloc = callocBytes 48
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 48 >=> wrapPtr ActionEntry)
    wrappedPtrFree = Just ptr_to_g_free

-- | Construct a `ActionEntry` struct initialized to zero.
newZeroActionEntry :: MonadIO m => m ActionEntry
newZeroActionEntry = liftIO $ wrappedPtrCalloc >>= wrapPtr ActionEntry

instance tag ~ 'AttrSet => Constructible ActionEntry tag where
    new _ attrs = do
        o <- newZeroActionEntry
        GI.Attributes.set o attrs
        return o


noActionEntry :: Maybe ActionEntry
noActionEntry = Nothing

getActionEntryName :: MonadIO m => ActionEntry -> m (Maybe T.Text)
getActionEntryName s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

setActionEntryName :: MonadIO m => ActionEntry -> CString -> m ()
setActionEntryName s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: CString)

clearActionEntryName :: MonadIO m => ActionEntry -> m ()
clearActionEntryName s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (FP.nullPtr :: CString)

data ActionEntryNameFieldInfo
instance AttrInfo ActionEntryNameFieldInfo where
    type AttrAllowedOps ActionEntryNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionEntryNameFieldInfo = (~) CString
    type AttrBaseTypeConstraint ActionEntryNameFieldInfo = (~) ActionEntry
    type AttrGetType ActionEntryNameFieldInfo = Maybe T.Text
    type AttrLabel ActionEntryNameFieldInfo = "name"
    type AttrOrigin ActionEntryNameFieldInfo = ActionEntry
    attrGet _ = getActionEntryName
    attrSet _ = setActionEntryName
    attrConstruct = undefined
    attrClear _ = clearActionEntryName

actionEntry_name :: AttrLabelProxy "name"
actionEntry_name = AttrLabelProxy


getActionEntryStockId :: MonadIO m => ActionEntry -> m (Maybe T.Text)
getActionEntryStockId s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

setActionEntryStockId :: MonadIO m => ActionEntry -> CString -> m ()
setActionEntryStockId s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: CString)

clearActionEntryStockId :: MonadIO m => ActionEntry -> m ()
clearActionEntryStockId s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: CString)

data ActionEntryStockIdFieldInfo
instance AttrInfo ActionEntryStockIdFieldInfo where
    type AttrAllowedOps ActionEntryStockIdFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionEntryStockIdFieldInfo = (~) CString
    type AttrBaseTypeConstraint ActionEntryStockIdFieldInfo = (~) ActionEntry
    type AttrGetType ActionEntryStockIdFieldInfo = Maybe T.Text
    type AttrLabel ActionEntryStockIdFieldInfo = "stock_id"
    type AttrOrigin ActionEntryStockIdFieldInfo = ActionEntry
    attrGet _ = getActionEntryStockId
    attrSet _ = setActionEntryStockId
    attrConstruct = undefined
    attrClear _ = clearActionEntryStockId

actionEntry_stockId :: AttrLabelProxy "stockId"
actionEntry_stockId = AttrLabelProxy


getActionEntryLabel :: MonadIO m => ActionEntry -> m (Maybe T.Text)
getActionEntryLabel s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

setActionEntryLabel :: MonadIO m => ActionEntry -> CString -> m ()
setActionEntryLabel s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: CString)

clearActionEntryLabel :: MonadIO m => ActionEntry -> m ()
clearActionEntryLabel s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (FP.nullPtr :: CString)

data ActionEntryLabelFieldInfo
instance AttrInfo ActionEntryLabelFieldInfo where
    type AttrAllowedOps ActionEntryLabelFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionEntryLabelFieldInfo = (~) CString
    type AttrBaseTypeConstraint ActionEntryLabelFieldInfo = (~) ActionEntry
    type AttrGetType ActionEntryLabelFieldInfo = Maybe T.Text
    type AttrLabel ActionEntryLabelFieldInfo = "label"
    type AttrOrigin ActionEntryLabelFieldInfo = ActionEntry
    attrGet _ = getActionEntryLabel
    attrSet _ = setActionEntryLabel
    attrConstruct = undefined
    attrClear _ = clearActionEntryLabel

actionEntry_label :: AttrLabelProxy "label"
actionEntry_label = AttrLabelProxy


getActionEntryAccelerator :: MonadIO m => ActionEntry -> m (Maybe T.Text)
getActionEntryAccelerator s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

setActionEntryAccelerator :: MonadIO m => ActionEntry -> CString -> m ()
setActionEntryAccelerator s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: CString)

clearActionEntryAccelerator :: MonadIO m => ActionEntry -> m ()
clearActionEntryAccelerator s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (FP.nullPtr :: CString)

data ActionEntryAcceleratorFieldInfo
instance AttrInfo ActionEntryAcceleratorFieldInfo where
    type AttrAllowedOps ActionEntryAcceleratorFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionEntryAcceleratorFieldInfo = (~) CString
    type AttrBaseTypeConstraint ActionEntryAcceleratorFieldInfo = (~) ActionEntry
    type AttrGetType ActionEntryAcceleratorFieldInfo = Maybe T.Text
    type AttrLabel ActionEntryAcceleratorFieldInfo = "accelerator"
    type AttrOrigin ActionEntryAcceleratorFieldInfo = ActionEntry
    attrGet _ = getActionEntryAccelerator
    attrSet _ = setActionEntryAccelerator
    attrConstruct = undefined
    attrClear _ = clearActionEntryAccelerator

actionEntry_accelerator :: AttrLabelProxy "accelerator"
actionEntry_accelerator = AttrLabelProxy


getActionEntryTooltip :: MonadIO m => ActionEntry -> m (Maybe T.Text)
getActionEntryTooltip s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

setActionEntryTooltip :: MonadIO m => ActionEntry -> CString -> m ()
setActionEntryTooltip s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (val :: CString)

clearActionEntryTooltip :: MonadIO m => ActionEntry -> m ()
clearActionEntryTooltip s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (FP.nullPtr :: CString)

data ActionEntryTooltipFieldInfo
instance AttrInfo ActionEntryTooltipFieldInfo where
    type AttrAllowedOps ActionEntryTooltipFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionEntryTooltipFieldInfo = (~) CString
    type AttrBaseTypeConstraint ActionEntryTooltipFieldInfo = (~) ActionEntry
    type AttrGetType ActionEntryTooltipFieldInfo = Maybe T.Text
    type AttrLabel ActionEntryTooltipFieldInfo = "tooltip"
    type AttrOrigin ActionEntryTooltipFieldInfo = ActionEntry
    attrGet _ = getActionEntryTooltip
    attrSet _ = setActionEntryTooltip
    attrConstruct = undefined
    attrClear _ = clearActionEntryTooltip

actionEntry_tooltip :: AttrLabelProxy "tooltip"
actionEntry_tooltip = AttrLabelProxy


getActionEntryCallback :: MonadIO m => ActionEntry -> m (Maybe GObject.Callbacks.Callback)
getActionEntryCallback s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO (FunPtr GObject.Callbacks.C_Callback)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GObject.Callbacks.dynamic_Callback val'
        return val''
    return result

setActionEntryCallback :: MonadIO m => ActionEntry -> FunPtr GObject.Callbacks.C_Callback -> m ()
setActionEntryCallback s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 40) (val :: FunPtr GObject.Callbacks.C_Callback)

clearActionEntryCallback :: MonadIO m => ActionEntry -> m ()
clearActionEntryCallback s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 40) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_Callback)

data ActionEntryCallbackFieldInfo
instance AttrInfo ActionEntryCallbackFieldInfo where
    type AttrAllowedOps ActionEntryCallbackFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionEntryCallbackFieldInfo = (~) (FunPtr GObject.Callbacks.C_Callback)
    type AttrBaseTypeConstraint ActionEntryCallbackFieldInfo = (~) ActionEntry
    type AttrGetType ActionEntryCallbackFieldInfo = Maybe GObject.Callbacks.Callback
    type AttrLabel ActionEntryCallbackFieldInfo = "callback"
    type AttrOrigin ActionEntryCallbackFieldInfo = ActionEntry
    attrGet _ = getActionEntryCallback
    attrSet _ = setActionEntryCallback
    attrConstruct = undefined
    attrClear _ = clearActionEntryCallback

actionEntry_callback :: AttrLabelProxy "callback"
actionEntry_callback = AttrLabelProxy



instance O.HasAttributeList ActionEntry
type instance O.AttributeList ActionEntry = ActionEntryAttributeList
type ActionEntryAttributeList = ('[ '("name", ActionEntryNameFieldInfo), '("stockId", ActionEntryStockIdFieldInfo), '("label", ActionEntryLabelFieldInfo), '("accelerator", ActionEntryAcceleratorFieldInfo), '("tooltip", ActionEntryTooltipFieldInfo), '("callback", ActionEntryCallbackFieldInfo)] :: [(Symbol, *)])

type family ResolveActionEntryMethod (t :: Symbol) (o :: *) :: * where
    ResolveActionEntryMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveActionEntryMethod t ActionEntry, O.MethodInfo info ActionEntry p) => O.IsLabelProxy t (ActionEntry -> p) where
    fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)

#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveActionEntryMethod t ActionEntry, O.MethodInfo info ActionEntry p) => O.IsLabel t (ActionEntry -> p) where
    fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif