{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- 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 'P.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.

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

module GI.Gio.Structs.ActionEntry
    ( 

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


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveActionEntryMethod                ,
#endif




 -- * Properties
-- ** activate #attr:activate#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    actionEntry_activate                    ,
#endif
    clearActionEntryActivate                ,
    getActionEntryActivate                  ,
    setActionEntryActivate                  ,


-- ** changeState #attr:changeState#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    actionEntry_changeState                 ,
#endif
    clearActionEntryChangeState             ,
    getActionEntryChangeState               ,
    setActionEntryChangeState               ,


-- ** name #attr:name#
-- | the name of the action

#if defined(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 'P.Nothing' for no parameter)

#if defined(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 'P.Nothing' here.

#if defined(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.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
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)
    deriving (ActionEntry -> ActionEntry -> Bool
(ActionEntry -> ActionEntry -> Bool)
-> (ActionEntry -> ActionEntry -> Bool) -> Eq ActionEntry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActionEntry -> ActionEntry -> Bool
$c/= :: ActionEntry -> ActionEntry -> Bool
== :: ActionEntry -> ActionEntry -> Bool
$c== :: ActionEntry -> ActionEntry -> Bool
Eq)
instance WrappedPtr ActionEntry where
    wrappedPtrCalloc :: IO (Ptr ActionEntry)
wrappedPtrCalloc = Int -> IO (Ptr ActionEntry)
forall a. Int -> IO (Ptr a)
callocBytes 64
    wrappedPtrCopy :: ActionEntry -> IO ActionEntry
wrappedPtrCopy = \p :: ActionEntry
p -> ActionEntry
-> (Ptr ActionEntry -> IO ActionEntry) -> IO ActionEntry
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionEntry
p (Int -> Ptr ActionEntry -> IO (Ptr ActionEntry)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 64 (Ptr ActionEntry -> IO (Ptr ActionEntry))
-> (Ptr ActionEntry -> IO ActionEntry)
-> Ptr ActionEntry
-> IO ActionEntry
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr ActionEntry -> ActionEntry)
-> Ptr ActionEntry -> IO ActionEntry
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr ActionEntry -> ActionEntry
ActionEntry)
    wrappedPtrFree :: Maybe (GDestroyNotify ActionEntry)
wrappedPtrFree = GDestroyNotify ActionEntry -> Maybe (GDestroyNotify ActionEntry)
forall a. a -> Maybe a
Just GDestroyNotify ActionEntry
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

-- | Construct a `ActionEntry` struct initialized to zero.
newZeroActionEntry :: MonadIO m => m ActionEntry
newZeroActionEntry :: m ActionEntry
newZeroActionEntry = IO ActionEntry -> m ActionEntry
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ActionEntry -> m ActionEntry)
-> IO ActionEntry -> m ActionEntry
forall a b. (a -> b) -> a -> b
$ IO (Ptr ActionEntry)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr ActionEntry)
-> (Ptr ActionEntry -> IO ActionEntry) -> IO ActionEntry
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr ActionEntry -> ActionEntry)
-> Ptr ActionEntry -> IO ActionEntry
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr ActionEntry -> ActionEntry
ActionEntry

instance tag ~ 'AttrSet => Constructible ActionEntry tag where
    new :: (ManagedPtr ActionEntry -> ActionEntry)
-> [AttrOp ActionEntry tag] -> m ActionEntry
new _ attrs :: [AttrOp ActionEntry tag]
attrs = do
        ActionEntry
o <- m ActionEntry
forall (m :: * -> *). MonadIO m => m ActionEntry
newZeroActionEntry
        ActionEntry -> [AttrOp ActionEntry 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set ActionEntry
o [AttrOp ActionEntry tag]
[AttrOp ActionEntry 'AttrSet]
attrs
        ActionEntry -> m ActionEntry
forall (m :: * -> *) a. Monad m => a -> m a
return ActionEntry
o


-- | A convenience alias for `Nothing` :: `Maybe` `ActionEntry`.
noActionEntry :: Maybe ActionEntry
noActionEntry :: Maybe ActionEntry
noActionEntry = Maybe ActionEntry
forall a. Maybe a
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 :: ActionEntry -> m (Maybe Text)
getActionEntryName s :: ActionEntry
s = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ ActionEntry
-> (Ptr ActionEntry -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionEntry
s ((Ptr ActionEntry -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr ActionEntry -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ActionEntry
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr ActionEntry
ptr Ptr ActionEntry -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \val' :: CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
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 :: ActionEntry -> CString -> m ()
setActionEntryName s :: ActionEntry
s val :: CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ActionEntry -> (Ptr ActionEntry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionEntry
s ((Ptr ActionEntry -> IO ()) -> IO ())
-> (Ptr ActionEntry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ActionEntry
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionEntry
ptr Ptr ActionEntry -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (CString
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 :: ActionEntry -> m ()
clearActionEntryName s :: ActionEntry
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ActionEntry -> (Ptr ActionEntry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionEntry
s ((Ptr ActionEntry -> IO ()) -> IO ())
-> (Ptr ActionEntry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ActionEntry
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionEntry
ptr Ptr ActionEntry -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (CString
forall a. Ptr a
FP.nullPtr :: CString)

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

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 :: ActionEntry
-> m (Maybe ActionEntryActivateFieldCallback_WithClosures)
getActionEntryActivate s :: ActionEntry
s = IO (Maybe ActionEntryActivateFieldCallback_WithClosures)
-> m (Maybe ActionEntryActivateFieldCallback_WithClosures)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ActionEntryActivateFieldCallback_WithClosures)
 -> m (Maybe ActionEntryActivateFieldCallback_WithClosures))
-> IO (Maybe ActionEntryActivateFieldCallback_WithClosures)
-> m (Maybe ActionEntryActivateFieldCallback_WithClosures)
forall a b. (a -> b) -> a -> b
$ ActionEntry
-> (Ptr ActionEntry
    -> IO (Maybe ActionEntryActivateFieldCallback_WithClosures))
-> IO (Maybe ActionEntryActivateFieldCallback_WithClosures)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionEntry
s ((Ptr ActionEntry
  -> IO (Maybe ActionEntryActivateFieldCallback_WithClosures))
 -> IO (Maybe ActionEntryActivateFieldCallback_WithClosures))
-> (Ptr ActionEntry
    -> IO (Maybe ActionEntryActivateFieldCallback_WithClosures))
-> IO (Maybe ActionEntryActivateFieldCallback_WithClosures)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ActionEntry
ptr -> do
    FunPtr C_ActionEntryActivateFieldCallback
val <- Ptr (FunPtr C_ActionEntryActivateFieldCallback)
-> IO (FunPtr C_ActionEntryActivateFieldCallback)
forall a. Storable a => Ptr a -> IO a
peek (Ptr ActionEntry
ptr Ptr ActionEntry
-> Int -> Ptr (FunPtr C_ActionEntryActivateFieldCallback)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) :: IO (FunPtr Gio.Callbacks.C_ActionEntryActivateFieldCallback)
    Maybe ActionEntryActivateFieldCallback_WithClosures
result <- FunPtr C_ActionEntryActivateFieldCallback
-> (FunPtr C_ActionEntryActivateFieldCallback
    -> IO ActionEntryActivateFieldCallback_WithClosures)
-> IO (Maybe ActionEntryActivateFieldCallback_WithClosures)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_ActionEntryActivateFieldCallback
val ((FunPtr C_ActionEntryActivateFieldCallback
  -> IO ActionEntryActivateFieldCallback_WithClosures)
 -> IO (Maybe ActionEntryActivateFieldCallback_WithClosures))
-> (FunPtr C_ActionEntryActivateFieldCallback
    -> IO ActionEntryActivateFieldCallback_WithClosures)
-> IO (Maybe ActionEntryActivateFieldCallback_WithClosures)
forall a b. (a -> b) -> a -> b
$ \val' :: FunPtr C_ActionEntryActivateFieldCallback
val' -> do
        let val'' :: ActionEntryActivateFieldCallback_WithClosures
val'' = FunPtr C_ActionEntryActivateFieldCallback
-> ActionEntryActivateFieldCallback_WithClosures
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSimpleAction a) =>
FunPtr C_ActionEntryActivateFieldCallback
-> a -> Maybe GVariant -> Ptr () -> m ()
Gio.Callbacks.dynamic_ActionEntryActivateFieldCallback FunPtr C_ActionEntryActivateFieldCallback
val'
        ActionEntryActivateFieldCallback_WithClosures
-> IO ActionEntryActivateFieldCallback_WithClosures
forall (m :: * -> *) a. Monad m => a -> m a
return ActionEntryActivateFieldCallback_WithClosures
val''
    Maybe ActionEntryActivateFieldCallback_WithClosures
-> IO (Maybe ActionEntryActivateFieldCallback_WithClosures)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ActionEntryActivateFieldCallback_WithClosures
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 :: ActionEntry -> FunPtr C_ActionEntryActivateFieldCallback -> m ()
setActionEntryActivate s :: ActionEntry
s val :: FunPtr C_ActionEntryActivateFieldCallback
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ActionEntry -> (Ptr ActionEntry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionEntry
s ((Ptr ActionEntry -> IO ()) -> IO ())
-> (Ptr ActionEntry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ActionEntry
ptr -> do
    Ptr (FunPtr C_ActionEntryActivateFieldCallback)
-> FunPtr C_ActionEntryActivateFieldCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionEntry
ptr Ptr ActionEntry
-> Int -> Ptr (FunPtr C_ActionEntryActivateFieldCallback)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (FunPtr C_ActionEntryActivateFieldCallback
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 :: ActionEntry -> m ()
clearActionEntryActivate s :: ActionEntry
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ActionEntry -> (Ptr ActionEntry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionEntry
s ((Ptr ActionEntry -> IO ()) -> IO ())
-> (Ptr ActionEntry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ActionEntry
ptr -> do
    Ptr (FunPtr C_ActionEntryActivateFieldCallback)
-> FunPtr C_ActionEntryActivateFieldCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionEntry
ptr Ptr ActionEntry
-> Int -> Ptr (FunPtr C_ActionEntryActivateFieldCallback)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (FunPtr C_ActionEntryActivateFieldCallback
forall a. FunPtr a
FP.nullFunPtr :: FunPtr Gio.Callbacks.C_ActionEntryActivateFieldCallback)

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

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 :: ActionEntry -> m (Maybe Text)
getActionEntryParameterType s :: ActionEntry
s = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ ActionEntry
-> (Ptr ActionEntry -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionEntry
s ((Ptr ActionEntry -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr ActionEntry -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ActionEntry
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr ActionEntry
ptr Ptr ActionEntry -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \val' :: CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
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 :: ActionEntry -> CString -> m ()
setActionEntryParameterType s :: ActionEntry
s val :: CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ActionEntry -> (Ptr ActionEntry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionEntry
s ((Ptr ActionEntry -> IO ()) -> IO ())
-> (Ptr ActionEntry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ActionEntry
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionEntry
ptr Ptr ActionEntry -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (CString
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 :: ActionEntry -> m ()
clearActionEntryParameterType s :: ActionEntry
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ActionEntry -> (Ptr ActionEntry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionEntry
s ((Ptr ActionEntry -> IO ()) -> IO ())
-> (Ptr ActionEntry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ActionEntry
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionEntry
ptr Ptr ActionEntry -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (CString
forall a. Ptr a
FP.nullPtr :: CString)

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

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 :: ActionEntry -> m (Maybe Text)
getActionEntryState s :: ActionEntry
s = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ ActionEntry
-> (Ptr ActionEntry -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionEntry
s ((Ptr ActionEntry -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr ActionEntry -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ActionEntry
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr ActionEntry
ptr Ptr ActionEntry -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \val' :: CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
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 :: ActionEntry -> CString -> m ()
setActionEntryState s :: ActionEntry
s val :: CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ActionEntry -> (Ptr ActionEntry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionEntry
s ((Ptr ActionEntry -> IO ()) -> IO ())
-> (Ptr ActionEntry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ActionEntry
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionEntry
ptr Ptr ActionEntry -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) (CString
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 :: ActionEntry -> m ()
clearActionEntryState s :: ActionEntry
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ActionEntry -> (Ptr ActionEntry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionEntry
s ((Ptr ActionEntry -> IO ()) -> IO ())
-> (Ptr ActionEntry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ActionEntry
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionEntry
ptr Ptr ActionEntry -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) (CString
forall a. Ptr a
FP.nullPtr :: CString)

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

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 :: ActionEntry
-> m (Maybe ActionEntryChangeStateFieldCallback_WithClosures)
getActionEntryChangeState s :: ActionEntry
s = IO (Maybe ActionEntryChangeStateFieldCallback_WithClosures)
-> m (Maybe ActionEntryChangeStateFieldCallback_WithClosures)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ActionEntryChangeStateFieldCallback_WithClosures)
 -> m (Maybe ActionEntryChangeStateFieldCallback_WithClosures))
-> IO (Maybe ActionEntryChangeStateFieldCallback_WithClosures)
-> m (Maybe ActionEntryChangeStateFieldCallback_WithClosures)
forall a b. (a -> b) -> a -> b
$ ActionEntry
-> (Ptr ActionEntry
    -> IO (Maybe ActionEntryChangeStateFieldCallback_WithClosures))
-> IO (Maybe ActionEntryChangeStateFieldCallback_WithClosures)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionEntry
s ((Ptr ActionEntry
  -> IO (Maybe ActionEntryChangeStateFieldCallback_WithClosures))
 -> IO (Maybe ActionEntryChangeStateFieldCallback_WithClosures))
-> (Ptr ActionEntry
    -> IO (Maybe ActionEntryChangeStateFieldCallback_WithClosures))
-> IO (Maybe ActionEntryChangeStateFieldCallback_WithClosures)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ActionEntry
ptr -> do
    FunPtr C_ActionEntryActivateFieldCallback
val <- Ptr (FunPtr C_ActionEntryActivateFieldCallback)
-> IO (FunPtr C_ActionEntryActivateFieldCallback)
forall a. Storable a => Ptr a -> IO a
peek (Ptr ActionEntry
ptr Ptr ActionEntry
-> Int -> Ptr (FunPtr C_ActionEntryActivateFieldCallback)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) :: IO (FunPtr Gio.Callbacks.C_ActionEntryChangeStateFieldCallback)
    Maybe ActionEntryChangeStateFieldCallback_WithClosures
result <- FunPtr C_ActionEntryActivateFieldCallback
-> (FunPtr C_ActionEntryActivateFieldCallback
    -> IO ActionEntryChangeStateFieldCallback_WithClosures)
-> IO (Maybe ActionEntryChangeStateFieldCallback_WithClosures)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_ActionEntryActivateFieldCallback
val ((FunPtr C_ActionEntryActivateFieldCallback
  -> IO ActionEntryChangeStateFieldCallback_WithClosures)
 -> IO (Maybe ActionEntryChangeStateFieldCallback_WithClosures))
-> (FunPtr C_ActionEntryActivateFieldCallback
    -> IO ActionEntryChangeStateFieldCallback_WithClosures)
-> IO (Maybe ActionEntryChangeStateFieldCallback_WithClosures)
forall a b. (a -> b) -> a -> b
$ \val' :: FunPtr C_ActionEntryActivateFieldCallback
val' -> do
        let val'' :: ActionEntryChangeStateFieldCallback_WithClosures
val'' = FunPtr C_ActionEntryActivateFieldCallback
-> ActionEntryChangeStateFieldCallback_WithClosures
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSimpleAction a) =>
FunPtr C_ActionEntryActivateFieldCallback
-> a -> GVariant -> Ptr () -> m ()
Gio.Callbacks.dynamic_ActionEntryChangeStateFieldCallback FunPtr C_ActionEntryActivateFieldCallback
val'
        ActionEntryChangeStateFieldCallback_WithClosures
-> IO ActionEntryChangeStateFieldCallback_WithClosures
forall (m :: * -> *) a. Monad m => a -> m a
return ActionEntryChangeStateFieldCallback_WithClosures
val''
    Maybe ActionEntryChangeStateFieldCallback_WithClosures
-> IO (Maybe ActionEntryChangeStateFieldCallback_WithClosures)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ActionEntryChangeStateFieldCallback_WithClosures
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 :: ActionEntry -> FunPtr C_ActionEntryActivateFieldCallback -> m ()
setActionEntryChangeState s :: ActionEntry
s val :: FunPtr C_ActionEntryActivateFieldCallback
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ActionEntry -> (Ptr ActionEntry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionEntry
s ((Ptr ActionEntry -> IO ()) -> IO ())
-> (Ptr ActionEntry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ActionEntry
ptr -> do
    Ptr (FunPtr C_ActionEntryActivateFieldCallback)
-> FunPtr C_ActionEntryActivateFieldCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionEntry
ptr Ptr ActionEntry
-> Int -> Ptr (FunPtr C_ActionEntryActivateFieldCallback)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) (FunPtr C_ActionEntryActivateFieldCallback
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 :: ActionEntry -> m ()
clearActionEntryChangeState s :: ActionEntry
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ActionEntry -> (Ptr ActionEntry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionEntry
s ((Ptr ActionEntry -> IO ()) -> IO ())
-> (Ptr ActionEntry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ActionEntry
ptr -> do
    Ptr (FunPtr C_ActionEntryActivateFieldCallback)
-> FunPtr C_ActionEntryActivateFieldCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionEntry
ptr Ptr ActionEntry
-> Int -> Ptr (FunPtr C_ActionEntryActivateFieldCallback)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) (FunPtr C_ActionEntryActivateFieldCallback
forall a. FunPtr a
FP.nullFunPtr :: FunPtr Gio.Callbacks.C_ActionEntryChangeStateFieldCallback)

#if defined(ENABLE_OVERLOADING)
data ActionEntryChangeStateFieldInfo
instance AttrInfo ActionEntryChangeStateFieldInfo where
    type AttrBaseTypeConstraint ActionEntryChangeStateFieldInfo = (~) ActionEntry
    type AttrAllowedOps ActionEntryChangeStateFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionEntryChangeStateFieldInfo = (~) (FunPtr Gio.Callbacks.C_ActionEntryChangeStateFieldCallback)
    type AttrTransferTypeConstraint ActionEntryChangeStateFieldInfo = (~)Gio.Callbacks.ActionEntryChangeStateFieldCallback_WithClosures
    type AttrTransferType ActionEntryChangeStateFieldInfo = (FunPtr Gio.Callbacks.C_ActionEntryChangeStateFieldCallback)
    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
    attrTransfer _ v = do
        Gio.Callbacks.mk_ActionEntryChangeStateFieldCallback (Gio.Callbacks.wrap_ActionEntryChangeStateFieldCallback Nothing v)

actionEntry_changeState :: AttrLabelProxy "changeState"
actionEntry_changeState = AttrLabelProxy

#endif



#if defined(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 defined(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 @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif