{-# LANGUAGE TypeApplications #-}


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

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

module GI.Gst.Structs.ClockEntry
    ( 

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


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveClockEntryMethod                 ,
#endif



 -- * Properties


-- ** refcount #attr:refcount#
-- | reference counter (read-only)

#if defined(ENABLE_OVERLOADING)
    clockEntry_refcount                     ,
#endif
    getClockEntryRefcount                   ,
    setClockEntryRefcount                   ,




    ) 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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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.Coerce as Coerce
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 GHC.Records as R


-- | Memory-managed wrapper type.
newtype ClockEntry = ClockEntry (SP.ManagedPtr ClockEntry)
    deriving (ClockEntry -> ClockEntry -> Bool
(ClockEntry -> ClockEntry -> Bool)
-> (ClockEntry -> ClockEntry -> Bool) -> Eq ClockEntry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClockEntry -> ClockEntry -> Bool
== :: ClockEntry -> ClockEntry -> Bool
$c/= :: ClockEntry -> ClockEntry -> Bool
/= :: ClockEntry -> ClockEntry -> Bool
Eq)

instance SP.ManagedPtrNewtype ClockEntry where
    toManagedPtr :: ClockEntry -> ManagedPtr ClockEntry
toManagedPtr (ClockEntry ManagedPtr ClockEntry
p) = ManagedPtr ClockEntry
p

instance BoxedPtr ClockEntry where
    boxedPtrCopy :: ClockEntry -> IO ClockEntry
boxedPtrCopy = \ClockEntry
p -> ClockEntry -> (Ptr ClockEntry -> IO ClockEntry) -> IO ClockEntry
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ClockEntry
p (Int -> Ptr ClockEntry -> IO (Ptr ClockEntry)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
112 (Ptr ClockEntry -> IO (Ptr ClockEntry))
-> (Ptr ClockEntry -> IO ClockEntry)
-> Ptr ClockEntry
-> IO ClockEntry
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr ClockEntry -> ClockEntry)
-> Ptr ClockEntry -> IO ClockEntry
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr ClockEntry -> ClockEntry
ClockEntry)
    boxedPtrFree :: ClockEntry -> IO ()
boxedPtrFree = \ClockEntry
x -> ClockEntry -> (Ptr ClockEntry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr ClockEntry
x Ptr ClockEntry -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr ClockEntry where
    boxedPtrCalloc :: IO (Ptr ClockEntry)
boxedPtrCalloc = Int -> IO (Ptr ClockEntry)
forall a. Int -> IO (Ptr a)
callocBytes Int
112


-- | Construct a `ClockEntry` struct initialized to zero.
newZeroClockEntry :: MonadIO m => m ClockEntry
newZeroClockEntry :: forall (m :: * -> *). MonadIO m => m ClockEntry
newZeroClockEntry = IO ClockEntry -> m ClockEntry
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ClockEntry -> m ClockEntry) -> IO ClockEntry -> m ClockEntry
forall a b. (a -> b) -> a -> b
$ IO (Ptr ClockEntry)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr ClockEntry)
-> (Ptr ClockEntry -> IO ClockEntry) -> IO ClockEntry
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr ClockEntry -> ClockEntry)
-> Ptr ClockEntry -> IO ClockEntry
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr ClockEntry -> ClockEntry
ClockEntry

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


-- | 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 :: forall (m :: * -> *). MonadIO m => ClockEntry -> m Int32
getClockEntryRefcount ClockEntry
s = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ ClockEntry -> (Ptr ClockEntry -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ClockEntry
s ((Ptr ClockEntry -> IO Int32) -> IO Int32)
-> (Ptr ClockEntry -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr ClockEntry
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr ClockEntry
ptr Ptr ClockEntry -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
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 :: forall (m :: * -> *). MonadIO m => ClockEntry -> Int32 -> m ()
setClockEntryRefcount ClockEntry
s Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ClockEntry -> (Ptr ClockEntry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ClockEntry
s ((Ptr ClockEntry -> IO ()) -> IO ())
-> (Ptr ClockEntry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ClockEntry
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ClockEntry
ptr Ptr ClockEntry -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data ClockEntryRefcountFieldInfo
instance AttrInfo ClockEntryRefcountFieldInfo where
    type AttrBaseTypeConstraint ClockEntryRefcountFieldInfo = (~) ClockEntry
    type AttrAllowedOps ClockEntryRefcountFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ClockEntryRefcountFieldInfo = (~) Int32
    type AttrTransferTypeConstraint ClockEntryRefcountFieldInfo = (~)Int32
    type AttrTransferType ClockEntryRefcountFieldInfo = Int32
    type AttrGetType ClockEntryRefcountFieldInfo = Int32
    type AttrLabel ClockEntryRefcountFieldInfo = "refcount"
    type AttrOrigin ClockEntryRefcountFieldInfo = ClockEntry
    attrGet = getClockEntryRefcount
    attrSet = setClockEntryRefcount
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gst.Structs.ClockEntry.refcount"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.26/docs/GI-Gst-Structs-ClockEntry.html#g:attr:refcount"
        })

clockEntry_refcount :: AttrLabelProxy "refcount"
clockEntry_refcount = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ClockEntry
type instance O.AttributeList ClockEntry = ClockEntryAttributeList
type ClockEntryAttributeList = ('[ '("refcount", ClockEntryRefcountFieldInfo)] :: [(Symbol, *)])
#endif

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

instance (info ~ ResolveClockEntryMethod t ClockEntry, O.OverloadedMethod info ClockEntry p) => OL.IsLabel t (ClockEntry -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveClockEntryMethod t ClockEntry, O.OverloadedMethod info ClockEntry p, R.HasField t ClockEntry p) => R.HasField t ClockEntry p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveClockEntryMethod t ClockEntry, O.OverloadedMethodInfo info ClockEntry) => OL.IsLabel t (O.MethodProxy info ClockEntry) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif