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

All pending timeouts or periodic notifies are converted into
an entry.
Note that GstClockEntry should be treated as an opaque structure. It must
not be extended or allocated using a custom allocator.
-}

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

module GI.Gst.Structs.ClockEntry
    (

-- * Exported types
    ClockEntry(..)                          ,
    newZeroClockEntry                       ,
    noClockEntry                            ,


 -- * Properties
-- ** clock #attr:clock#
{- | /No description available in the introspection data./
-}
    clearClockEntryClock                    ,
#if ENABLE_OVERLOADING
    clockEntry_clock                        ,
#endif
    getClockEntryClock                      ,
    setClockEntryClock                      ,


-- ** destroyData #attr:destroyData#
{- | /No description available in the introspection data./
-}
    clearClockEntryDestroyData              ,
#if ENABLE_OVERLOADING
    clockEntry_destroyData                  ,
#endif
    getClockEntryDestroyData                ,
    setClockEntryDestroyData                ,


-- ** func #attr:func#
{- | /No description available in the introspection data./
-}
    clearClockEntryFunc                     ,
#if ENABLE_OVERLOADING
    clockEntry_func                         ,
#endif
    getClockEntryFunc                       ,
    setClockEntryFunc                       ,


-- ** interval #attr:interval#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    clockEntry_interval                     ,
#endif
    getClockEntryInterval                   ,
    setClockEntryInterval                   ,


-- ** refcount #attr:refcount#
{- | reference counter (read-only)
-}
#if ENABLE_OVERLOADING
    clockEntry_refcount                     ,
#endif
    getClockEntryRefcount                   ,
    setClockEntryRefcount                   ,


-- ** status #attr:status#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    clockEntry_status                       ,
#endif
    getClockEntryStatus                     ,
    setClockEntryStatus                     ,


-- ** time #attr:time#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    clockEntry_time                         ,
#endif
    getClockEntryTime                       ,
    setClockEntryTime                       ,


-- ** type #attr:type#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    clockEntry_type                         ,
#endif
    getClockEntryType                       ,
    setClockEntryType                       ,


-- ** unscheduled #attr:unscheduled#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    clockEntry_unscheduled                  ,
#endif
    getClockEntryUnscheduled                ,
    setClockEntryUnscheduled                ,


-- ** userData #attr:userData#
{- | /No description available in the introspection data./
-}
    clearClockEntryUserData                 ,
#if ENABLE_OVERLOADING
    clockEntry_userData                     ,
#endif
    getClockEntryUserData                   ,
    setClockEntryUserData                   ,


-- ** wokenUp #attr:wokenUp#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    clockEntry_wokenUp                      ,
#endif
    getClockEntryWokenUp                    ,
    setClockEntryWokenUp                    ,




    ) 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.GLib.Callbacks as GLib.Callbacks
import qualified GI.Gst.Callbacks as Gst.Callbacks
import {-# SOURCE #-} qualified GI.Gst.Enums as Gst.Enums
import {-# SOURCE #-} qualified GI.Gst.Objects.Clock as Gst.Clock

-- | Memory-managed wrapper type.
newtype ClockEntry = ClockEntry (ManagedPtr ClockEntry)
instance WrappedPtr ClockEntry where
    wrappedPtrCalloc = callocBytes 112
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 112 >=> wrapPtr ClockEntry)
    wrappedPtrFree = Just ptr_to_g_free

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `ClockEntry`.
noClockEntry :: Maybe ClockEntry
noClockEntry = Nothing

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

@
'Data.GI.Base.Attributes.get' clockEntry #refcount
@
-}
getClockEntryRefcount :: MonadIO m => ClockEntry -> m Int32
getClockEntryRefcount s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO Int32
    return val

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

@
'Data.GI.Base.Attributes.set' clockEntry [ #refcount 'Data.GI.Base.Attributes.:=' value ]
@
-}
setClockEntryRefcount :: MonadIO m => ClockEntry -> Int32 -> m ()
setClockEntryRefcount s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Int32)

#if ENABLE_OVERLOADING
data ClockEntryRefcountFieldInfo
instance AttrInfo ClockEntryRefcountFieldInfo where
    type AttrAllowedOps ClockEntryRefcountFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ClockEntryRefcountFieldInfo = (~) Int32
    type AttrBaseTypeConstraint ClockEntryRefcountFieldInfo = (~) ClockEntry
    type AttrGetType ClockEntryRefcountFieldInfo = Int32
    type AttrLabel ClockEntryRefcountFieldInfo = "refcount"
    type AttrOrigin ClockEntryRefcountFieldInfo = ClockEntry
    attrGet _ = getClockEntryRefcount
    attrSet _ = setClockEntryRefcount
    attrConstruct = undefined
    attrClear _ = undefined

clockEntry_refcount :: AttrLabelProxy "refcount"
clockEntry_refcount = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' clockEntry #clock
@
-}
getClockEntryClock :: MonadIO m => ClockEntry -> m (Maybe Gst.Clock.Clock)
getClockEntryClock s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO (Ptr Gst.Clock.Clock)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newObject Gst.Clock.Clock) val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' clockEntry [ #clock 'Data.GI.Base.Attributes.:=' value ]
@
-}
setClockEntryClock :: MonadIO m => ClockEntry -> Ptr Gst.Clock.Clock -> m ()
setClockEntryClock s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: Ptr Gst.Clock.Clock)

{- |
Set the value of the “@clock@” 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' #clock
@
-}
clearClockEntryClock :: MonadIO m => ClockEntry -> m ()
clearClockEntryClock s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gst.Clock.Clock)

#if ENABLE_OVERLOADING
data ClockEntryClockFieldInfo
instance AttrInfo ClockEntryClockFieldInfo where
    type AttrAllowedOps ClockEntryClockFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ClockEntryClockFieldInfo = (~) (Ptr Gst.Clock.Clock)
    type AttrBaseTypeConstraint ClockEntryClockFieldInfo = (~) ClockEntry
    type AttrGetType ClockEntryClockFieldInfo = Maybe Gst.Clock.Clock
    type AttrLabel ClockEntryClockFieldInfo = "clock"
    type AttrOrigin ClockEntryClockFieldInfo = ClockEntry
    attrGet _ = getClockEntryClock
    attrSet _ = setClockEntryClock
    attrConstruct = undefined
    attrClear _ = clearClockEntryClock

clockEntry_clock :: AttrLabelProxy "clock"
clockEntry_clock = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' clockEntry #type
@
-}
getClockEntryType :: MonadIO m => ClockEntry -> m Gst.Enums.ClockEntryType
getClockEntryType s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

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

@
'Data.GI.Base.Attributes.set' clockEntry [ #type 'Data.GI.Base.Attributes.:=' value ]
@
-}
setClockEntryType :: MonadIO m => ClockEntry -> Gst.Enums.ClockEntryType -> m ()
setClockEntryType s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 16) (val' :: CUInt)

#if ENABLE_OVERLOADING
data ClockEntryTypeFieldInfo
instance AttrInfo ClockEntryTypeFieldInfo where
    type AttrAllowedOps ClockEntryTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ClockEntryTypeFieldInfo = (~) Gst.Enums.ClockEntryType
    type AttrBaseTypeConstraint ClockEntryTypeFieldInfo = (~) ClockEntry
    type AttrGetType ClockEntryTypeFieldInfo = Gst.Enums.ClockEntryType
    type AttrLabel ClockEntryTypeFieldInfo = "type"
    type AttrOrigin ClockEntryTypeFieldInfo = ClockEntry
    attrGet _ = getClockEntryType
    attrSet _ = setClockEntryType
    attrConstruct = undefined
    attrClear _ = undefined

clockEntry_type :: AttrLabelProxy "type"
clockEntry_type = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' clockEntry #time
@
-}
getClockEntryTime :: MonadIO m => ClockEntry -> m Word64
getClockEntryTime s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO Word64
    return val

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

@
'Data.GI.Base.Attributes.set' clockEntry [ #time 'Data.GI.Base.Attributes.:=' value ]
@
-}
setClockEntryTime :: MonadIO m => ClockEntry -> Word64 -> m ()
setClockEntryTime s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: Word64)

#if ENABLE_OVERLOADING
data ClockEntryTimeFieldInfo
instance AttrInfo ClockEntryTimeFieldInfo where
    type AttrAllowedOps ClockEntryTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ClockEntryTimeFieldInfo = (~) Word64
    type AttrBaseTypeConstraint ClockEntryTimeFieldInfo = (~) ClockEntry
    type AttrGetType ClockEntryTimeFieldInfo = Word64
    type AttrLabel ClockEntryTimeFieldInfo = "time"
    type AttrOrigin ClockEntryTimeFieldInfo = ClockEntry
    attrGet _ = getClockEntryTime
    attrSet _ = setClockEntryTime
    attrConstruct = undefined
    attrClear _ = undefined

clockEntry_time :: AttrLabelProxy "time"
clockEntry_time = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' clockEntry #interval
@
-}
getClockEntryInterval :: MonadIO m => ClockEntry -> m Word64
getClockEntryInterval s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO Word64
    return val

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

@
'Data.GI.Base.Attributes.set' clockEntry [ #interval 'Data.GI.Base.Attributes.:=' value ]
@
-}
setClockEntryInterval :: MonadIO m => ClockEntry -> Word64 -> m ()
setClockEntryInterval s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (val :: Word64)

#if ENABLE_OVERLOADING
data ClockEntryIntervalFieldInfo
instance AttrInfo ClockEntryIntervalFieldInfo where
    type AttrAllowedOps ClockEntryIntervalFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ClockEntryIntervalFieldInfo = (~) Word64
    type AttrBaseTypeConstraint ClockEntryIntervalFieldInfo = (~) ClockEntry
    type AttrGetType ClockEntryIntervalFieldInfo = Word64
    type AttrLabel ClockEntryIntervalFieldInfo = "interval"
    type AttrOrigin ClockEntryIntervalFieldInfo = ClockEntry
    attrGet _ = getClockEntryInterval
    attrSet _ = setClockEntryInterval
    attrConstruct = undefined
    attrClear _ = undefined

clockEntry_interval :: AttrLabelProxy "interval"
clockEntry_interval = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' clockEntry #status
@
-}
getClockEntryStatus :: MonadIO m => ClockEntry -> m Gst.Enums.ClockReturn
getClockEntryStatus s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

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

@
'Data.GI.Base.Attributes.set' clockEntry [ #status 'Data.GI.Base.Attributes.:=' value ]
@
-}
setClockEntryStatus :: MonadIO m => ClockEntry -> Gst.Enums.ClockReturn -> m ()
setClockEntryStatus s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 40) (val' :: CUInt)

#if ENABLE_OVERLOADING
data ClockEntryStatusFieldInfo
instance AttrInfo ClockEntryStatusFieldInfo where
    type AttrAllowedOps ClockEntryStatusFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ClockEntryStatusFieldInfo = (~) Gst.Enums.ClockReturn
    type AttrBaseTypeConstraint ClockEntryStatusFieldInfo = (~) ClockEntry
    type AttrGetType ClockEntryStatusFieldInfo = Gst.Enums.ClockReturn
    type AttrLabel ClockEntryStatusFieldInfo = "status"
    type AttrOrigin ClockEntryStatusFieldInfo = ClockEntry
    attrGet _ = getClockEntryStatus
    attrSet _ = setClockEntryStatus
    attrConstruct = undefined
    attrClear _ = undefined

clockEntry_status :: AttrLabelProxy "status"
clockEntry_status = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' clockEntry #func
@
-}
getClockEntryFunc :: MonadIO m => ClockEntry -> m (Maybe Gst.Callbacks.ClockCallback_WithClosures)
getClockEntryFunc s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 48) :: IO (FunPtr Gst.Callbacks.C_ClockCallback)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = Gst.Callbacks.dynamic_ClockCallback val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' clockEntry [ #func 'Data.GI.Base.Attributes.:=' value ]
@
-}
setClockEntryFunc :: MonadIO m => ClockEntry -> FunPtr Gst.Callbacks.C_ClockCallback -> m ()
setClockEntryFunc s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 48) (val :: FunPtr Gst.Callbacks.C_ClockCallback)

{- |
Set the value of the “@func@” 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' #func
@
-}
clearClockEntryFunc :: MonadIO m => ClockEntry -> m ()
clearClockEntryFunc s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 48) (FP.nullFunPtr :: FunPtr Gst.Callbacks.C_ClockCallback)

#if ENABLE_OVERLOADING
data ClockEntryFuncFieldInfo
instance AttrInfo ClockEntryFuncFieldInfo where
    type AttrAllowedOps ClockEntryFuncFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ClockEntryFuncFieldInfo = (~) (FunPtr Gst.Callbacks.C_ClockCallback)
    type AttrBaseTypeConstraint ClockEntryFuncFieldInfo = (~) ClockEntry
    type AttrGetType ClockEntryFuncFieldInfo = Maybe Gst.Callbacks.ClockCallback_WithClosures
    type AttrLabel ClockEntryFuncFieldInfo = "func"
    type AttrOrigin ClockEntryFuncFieldInfo = ClockEntry
    attrGet _ = getClockEntryFunc
    attrSet _ = setClockEntryFunc
    attrConstruct = undefined
    attrClear _ = clearClockEntryFunc

clockEntry_func :: AttrLabelProxy "func"
clockEntry_func = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' clockEntry #userData
@
-}
getClockEntryUserData :: MonadIO m => ClockEntry -> m (Ptr ())
getClockEntryUserData s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 56) :: IO (Ptr ())
    return val

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

@
'Data.GI.Base.Attributes.set' clockEntry [ #userData 'Data.GI.Base.Attributes.:=' value ]
@
-}
setClockEntryUserData :: MonadIO m => ClockEntry -> Ptr () -> m ()
setClockEntryUserData s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 56) (val :: Ptr ())

{- |
Set the value of the “@user_data@” 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' #userData
@
-}
clearClockEntryUserData :: MonadIO m => ClockEntry -> m ()
clearClockEntryUserData s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 56) (FP.nullPtr :: Ptr ())

#if ENABLE_OVERLOADING
data ClockEntryUserDataFieldInfo
instance AttrInfo ClockEntryUserDataFieldInfo where
    type AttrAllowedOps ClockEntryUserDataFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ClockEntryUserDataFieldInfo = (~) (Ptr ())
    type AttrBaseTypeConstraint ClockEntryUserDataFieldInfo = (~) ClockEntry
    type AttrGetType ClockEntryUserDataFieldInfo = Ptr ()
    type AttrLabel ClockEntryUserDataFieldInfo = "user_data"
    type AttrOrigin ClockEntryUserDataFieldInfo = ClockEntry
    attrGet _ = getClockEntryUserData
    attrSet _ = setClockEntryUserData
    attrConstruct = undefined
    attrClear _ = clearClockEntryUserData

clockEntry_userData :: AttrLabelProxy "userData"
clockEntry_userData = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' clockEntry #destroyData
@
-}
getClockEntryDestroyData :: MonadIO m => ClockEntry -> m (Maybe GLib.Callbacks.DestroyNotify)
getClockEntryDestroyData s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 64) :: IO (FunPtr GLib.Callbacks.C_DestroyNotify)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GLib.Callbacks.dynamic_DestroyNotify val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' clockEntry [ #destroyData 'Data.GI.Base.Attributes.:=' value ]
@
-}
setClockEntryDestroyData :: MonadIO m => ClockEntry -> FunPtr GLib.Callbacks.C_DestroyNotify -> m ()
setClockEntryDestroyData s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 64) (val :: FunPtr GLib.Callbacks.C_DestroyNotify)

{- |
Set the value of the “@destroy_data@” 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' #destroyData
@
-}
clearClockEntryDestroyData :: MonadIO m => ClockEntry -> m ()
clearClockEntryDestroyData s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 64) (FP.nullFunPtr :: FunPtr GLib.Callbacks.C_DestroyNotify)

#if ENABLE_OVERLOADING
data ClockEntryDestroyDataFieldInfo
instance AttrInfo ClockEntryDestroyDataFieldInfo where
    type AttrAllowedOps ClockEntryDestroyDataFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ClockEntryDestroyDataFieldInfo = (~) (FunPtr GLib.Callbacks.C_DestroyNotify)
    type AttrBaseTypeConstraint ClockEntryDestroyDataFieldInfo = (~) ClockEntry
    type AttrGetType ClockEntryDestroyDataFieldInfo = Maybe GLib.Callbacks.DestroyNotify
    type AttrLabel ClockEntryDestroyDataFieldInfo = "destroy_data"
    type AttrOrigin ClockEntryDestroyDataFieldInfo = ClockEntry
    attrGet _ = getClockEntryDestroyData
    attrSet _ = setClockEntryDestroyData
    attrConstruct = undefined
    attrClear _ = clearClockEntryDestroyData

clockEntry_destroyData :: AttrLabelProxy "destroyData"
clockEntry_destroyData = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' clockEntry #unscheduled
@
-}
getClockEntryUnscheduled :: MonadIO m => ClockEntry -> m Bool
getClockEntryUnscheduled s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 72) :: IO CInt
    let val' = (/= 0) val
    return val'

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

@
'Data.GI.Base.Attributes.set' clockEntry [ #unscheduled 'Data.GI.Base.Attributes.:=' value ]
@
-}
setClockEntryUnscheduled :: MonadIO m => ClockEntry -> Bool -> m ()
setClockEntryUnscheduled s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 72) (val' :: CInt)

#if ENABLE_OVERLOADING
data ClockEntryUnscheduledFieldInfo
instance AttrInfo ClockEntryUnscheduledFieldInfo where
    type AttrAllowedOps ClockEntryUnscheduledFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ClockEntryUnscheduledFieldInfo = (~) Bool
    type AttrBaseTypeConstraint ClockEntryUnscheduledFieldInfo = (~) ClockEntry
    type AttrGetType ClockEntryUnscheduledFieldInfo = Bool
    type AttrLabel ClockEntryUnscheduledFieldInfo = "unscheduled"
    type AttrOrigin ClockEntryUnscheduledFieldInfo = ClockEntry
    attrGet _ = getClockEntryUnscheduled
    attrSet _ = setClockEntryUnscheduled
    attrConstruct = undefined
    attrClear _ = undefined

clockEntry_unscheduled :: AttrLabelProxy "unscheduled"
clockEntry_unscheduled = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' clockEntry #wokenUp
@
-}
getClockEntryWokenUp :: MonadIO m => ClockEntry -> m Bool
getClockEntryWokenUp s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 76) :: IO CInt
    let val' = (/= 0) val
    return val'

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

@
'Data.GI.Base.Attributes.set' clockEntry [ #wokenUp 'Data.GI.Base.Attributes.:=' value ]
@
-}
setClockEntryWokenUp :: MonadIO m => ClockEntry -> Bool -> m ()
setClockEntryWokenUp s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 76) (val' :: CInt)

#if ENABLE_OVERLOADING
data ClockEntryWokenUpFieldInfo
instance AttrInfo ClockEntryWokenUpFieldInfo where
    type AttrAllowedOps ClockEntryWokenUpFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ClockEntryWokenUpFieldInfo = (~) Bool
    type AttrBaseTypeConstraint ClockEntryWokenUpFieldInfo = (~) ClockEntry
    type AttrGetType ClockEntryWokenUpFieldInfo = Bool
    type AttrLabel ClockEntryWokenUpFieldInfo = "woken_up"
    type AttrOrigin ClockEntryWokenUpFieldInfo = ClockEntry
    attrGet _ = getClockEntryWokenUp
    attrSet _ = setClockEntryWokenUp
    attrConstruct = undefined
    attrClear _ = undefined

clockEntry_wokenUp :: AttrLabelProxy "wokenUp"
clockEntry_wokenUp = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList ClockEntry
type instance O.AttributeList ClockEntry = ClockEntryAttributeList
type ClockEntryAttributeList = ('[ '("refcount", ClockEntryRefcountFieldInfo), '("clock", ClockEntryClockFieldInfo), '("type", ClockEntryTypeFieldInfo), '("time", ClockEntryTimeFieldInfo), '("interval", ClockEntryIntervalFieldInfo), '("status", ClockEntryStatusFieldInfo), '("func", ClockEntryFuncFieldInfo), '("userData", ClockEntryUserDataFieldInfo), '("destroyData", ClockEntryDestroyDataFieldInfo), '("unscheduled", ClockEntryUnscheduledFieldInfo), '("wokenUp", ClockEntryWokenUpFieldInfo)] :: [(Symbol, *)])
#endif

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

instance (info ~ ResolveClockEntryMethod t ClockEntry, O.MethodInfo info ClockEntry p) => OL.IsLabel t (ClockEntry -> 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