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

This struct defines a single action.  It is for use with
'GI.Gio.Interfaces.ActionMap.actionMapAddActionEntries'.

The order of the items in the structure are intended to reflect
frequency of use.  It is permissible to use an incomplete initialiser
in order to leave some of the later values as 'Nothing'.  All values
after /@name@/ are optional.  Additional optional fields may be added in
the future.

See 'GI.Gio.Interfaces.ActionMap.actionMapAddActionEntries' for an example.
-}

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

module GI.Gio.Structs.ActionEntry
    (

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


 -- * Properties
-- ** activate #attr:activate#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    actionEntry_activate                    ,
#endif
    clearActionEntryActivate                ,
    getActionEntryActivate                  ,
    setActionEntryActivate                  ,


-- ** changeState #attr:changeState#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    actionEntry_changeState                 ,
#endif
    clearActionEntryChangeState             ,
    getActionEntryChangeState               ,
    setActionEntryChangeState               ,


-- ** name #attr:name#
{- | the name of the action
-}
#if ENABLE_OVERLOADING
    actionEntry_name                        ,
#endif
    clearActionEntryName                    ,
    getActionEntryName                      ,
    setActionEntryName                      ,


-- ** parameterType #attr:parameterType#
{- | the type of the parameter that must be passed to the
                 activate function for this action, given as a single
                 GVariant type string (or 'Nothing' for no parameter)
-}
#if ENABLE_OVERLOADING
    actionEntry_parameterType               ,
#endif
    clearActionEntryParameterType           ,
    getActionEntryParameterType             ,
    setActionEntryParameterType             ,


-- ** state #attr:state#
{- | the initial state for this action, given in
        [GVariant text format][gvariant-text].  The state is parsed
        with no extra type information, so type tags must be added to
        the string if they are necessary.  Stateless actions should
        give 'Nothing' here.
-}
#if ENABLE_OVERLOADING
    actionEntry_state                       ,
#endif
    clearActionEntryState                   ,
    getActionEntryState                     ,
    setActionEntryState                     ,




    ) 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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
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.Text as T
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 GI.Gio.Callbacks as Gio.Callbacks

-- | Memory-managed wrapper type.
newtype ActionEntry = ActionEntry (ManagedPtr ActionEntry)
instance WrappedPtr ActionEntry where
    wrappedPtrCalloc = callocBytes 64
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 64 >=> 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


-- | A convenience alias for `Nothing` :: `Maybe` `ActionEntry`.
noActionEntry :: Maybe ActionEntry
noActionEntry = Nothing

{- |
Get the value of the “@name@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' actionEntry #name
@
-}
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

{- |
Set the value of the “@name@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' actionEntry [ #name 'Data.GI.Base.Attributes.:=' value ]
@
-}
setActionEntryName :: MonadIO m => ActionEntry -> CString -> m ()
setActionEntryName s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: CString)

{- |
Set the value of the “@name@” field to `Nothing`.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.clear' #name
@
-}
clearActionEntryName :: MonadIO m => ActionEntry -> m ()
clearActionEntryName s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
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

#endif


{- |
Get the value of the “@activate@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' actionEntry #activate
@
-}
getActionEntryActivate :: MonadIO m => ActionEntry -> m (Maybe Gio.Callbacks.ActionEntryActivateFieldCallback_WithClosures)
getActionEntryActivate s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO (FunPtr Gio.Callbacks.C_ActionEntryActivateFieldCallback)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = Gio.Callbacks.dynamic_ActionEntryActivateFieldCallback val'
        return val''
    return result

{- |
Set the value of the “@activate@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' actionEntry [ #activate 'Data.GI.Base.Attributes.:=' value ]
@
-}
setActionEntryActivate :: MonadIO m => ActionEntry -> FunPtr Gio.Callbacks.C_ActionEntryActivateFieldCallback -> m ()
setActionEntryActivate s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: FunPtr Gio.Callbacks.C_ActionEntryActivateFieldCallback)

{- |
Set the value of the “@activate@” field to `Nothing`.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.clear' #activate
@
-}
clearActionEntryActivate :: MonadIO m => ActionEntry -> m ()
clearActionEntryActivate s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullFunPtr :: FunPtr Gio.Callbacks.C_ActionEntryActivateFieldCallback)

#if ENABLE_OVERLOADING
data ActionEntryActivateFieldInfo
instance AttrInfo ActionEntryActivateFieldInfo where
    type AttrAllowedOps ActionEntryActivateFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionEntryActivateFieldInfo = (~) (FunPtr Gio.Callbacks.C_ActionEntryActivateFieldCallback)
    type AttrBaseTypeConstraint ActionEntryActivateFieldInfo = (~) ActionEntry
    type AttrGetType ActionEntryActivateFieldInfo = Maybe Gio.Callbacks.ActionEntryActivateFieldCallback_WithClosures
    type AttrLabel ActionEntryActivateFieldInfo = "activate"
    type AttrOrigin ActionEntryActivateFieldInfo = ActionEntry
    attrGet _ = getActionEntryActivate
    attrSet _ = setActionEntryActivate
    attrConstruct = undefined
    attrClear _ = clearActionEntryActivate

actionEntry_activate :: AttrLabelProxy "activate"
actionEntry_activate = AttrLabelProxy

#endif


{- |
Get the value of the “@parameter_type@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' actionEntry #parameterType
@
-}
getActionEntryParameterType :: MonadIO m => ActionEntry -> m (Maybe T.Text)
getActionEntryParameterType 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

{- |
Set the value of the “@parameter_type@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' actionEntry [ #parameterType 'Data.GI.Base.Attributes.:=' value ]
@
-}
setActionEntryParameterType :: MonadIO m => ActionEntry -> CString -> m ()
setActionEntryParameterType s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: CString)

{- |
Set the value of the “@parameter_type@” field to `Nothing`.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.clear' #parameterType
@
-}
clearActionEntryParameterType :: MonadIO m => ActionEntry -> m ()
clearActionEntryParameterType s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data ActionEntryParameterTypeFieldInfo
instance AttrInfo ActionEntryParameterTypeFieldInfo where
    type AttrAllowedOps ActionEntryParameterTypeFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionEntryParameterTypeFieldInfo = (~) CString
    type AttrBaseTypeConstraint ActionEntryParameterTypeFieldInfo = (~) ActionEntry
    type AttrGetType ActionEntryParameterTypeFieldInfo = Maybe T.Text
    type AttrLabel ActionEntryParameterTypeFieldInfo = "parameter_type"
    type AttrOrigin ActionEntryParameterTypeFieldInfo = ActionEntry
    attrGet _ = getActionEntryParameterType
    attrSet _ = setActionEntryParameterType
    attrConstruct = undefined
    attrClear _ = clearActionEntryParameterType

actionEntry_parameterType :: AttrLabelProxy "parameterType"
actionEntry_parameterType = AttrLabelProxy

#endif


{- |
Get the value of the “@state@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' actionEntry #state
@
-}
getActionEntryState :: MonadIO m => ActionEntry -> m (Maybe T.Text)
getActionEntryState 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

{- |
Set the value of the “@state@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' actionEntry [ #state 'Data.GI.Base.Attributes.:=' value ]
@
-}
setActionEntryState :: MonadIO m => ActionEntry -> CString -> m ()
setActionEntryState s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: CString)

{- |
Set the value of the “@state@” field to `Nothing`.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.clear' #state
@
-}
clearActionEntryState :: MonadIO m => ActionEntry -> m ()
clearActionEntryState s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data ActionEntryStateFieldInfo
instance AttrInfo ActionEntryStateFieldInfo where
    type AttrAllowedOps ActionEntryStateFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionEntryStateFieldInfo = (~) CString
    type AttrBaseTypeConstraint ActionEntryStateFieldInfo = (~) ActionEntry
    type AttrGetType ActionEntryStateFieldInfo = Maybe T.Text
    type AttrLabel ActionEntryStateFieldInfo = "state"
    type AttrOrigin ActionEntryStateFieldInfo = ActionEntry
    attrGet _ = getActionEntryState
    attrSet _ = setActionEntryState
    attrConstruct = undefined
    attrClear _ = clearActionEntryState

actionEntry_state :: AttrLabelProxy "state"
actionEntry_state = AttrLabelProxy

#endif


{- |
Get the value of the “@change_state@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' actionEntry #changeState
@
-}
getActionEntryChangeState :: MonadIO m => ActionEntry -> m (Maybe Gio.Callbacks.ActionEntryChangeStateFieldCallback_WithClosures)
getActionEntryChangeState s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO (FunPtr Gio.Callbacks.C_ActionEntryChangeStateFieldCallback)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = Gio.Callbacks.dynamic_ActionEntryChangeStateFieldCallback val'
        return val''
    return result

{- |
Set the value of the “@change_state@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' actionEntry [ #changeState 'Data.GI.Base.Attributes.:=' value ]
@
-}
setActionEntryChangeState :: MonadIO m => ActionEntry -> FunPtr Gio.Callbacks.C_ActionEntryChangeStateFieldCallback -> m ()
setActionEntryChangeState s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (val :: FunPtr Gio.Callbacks.C_ActionEntryChangeStateFieldCallback)

{- |
Set the value of the “@change_state@” field to `Nothing`.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.clear' #changeState
@
-}
clearActionEntryChangeState :: MonadIO m => ActionEntry -> m ()
clearActionEntryChangeState s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (FP.nullFunPtr :: FunPtr Gio.Callbacks.C_ActionEntryChangeStateFieldCallback)

#if ENABLE_OVERLOADING
data ActionEntryChangeStateFieldInfo
instance AttrInfo ActionEntryChangeStateFieldInfo where
    type AttrAllowedOps ActionEntryChangeStateFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionEntryChangeStateFieldInfo = (~) (FunPtr Gio.Callbacks.C_ActionEntryChangeStateFieldCallback)
    type AttrBaseTypeConstraint ActionEntryChangeStateFieldInfo = (~) ActionEntry
    type AttrGetType ActionEntryChangeStateFieldInfo = Maybe Gio.Callbacks.ActionEntryChangeStateFieldCallback_WithClosures
    type AttrLabel ActionEntryChangeStateFieldInfo = "change_state"
    type AttrOrigin ActionEntryChangeStateFieldInfo = ActionEntry
    attrGet _ = getActionEntryChangeState
    attrSet _ = setActionEntryChangeState
    attrConstruct = undefined
    attrClear _ = clearActionEntryChangeState

actionEntry_changeState :: AttrLabelProxy "changeState"
actionEntry_changeState = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList ActionEntry
type instance O.AttributeList ActionEntry = ActionEntryAttributeList
type ActionEntryAttributeList = ('[ '("name", ActionEntryNameFieldInfo), '("activate", ActionEntryActivateFieldInfo), '("parameterType", ActionEntryParameterTypeFieldInfo), '("state", ActionEntryStateFieldInfo), '("changeState", ActionEntryChangeStateFieldInfo)] :: [(Symbol, *)])
#endif

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

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

#endif