{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gst.Structs.MetaTransformCopy
(
MetaTransformCopy(..) ,
newZeroMetaTransformCopy ,
#if defined(ENABLE_OVERLOADING)
ResolveMetaTransformCopyMethod ,
#endif
getMetaTransformCopyOffset ,
#if defined(ENABLE_OVERLOADING)
metaTransformCopy_offset ,
#endif
setMetaTransformCopyOffset ,
getMetaTransformCopyRegion ,
#if defined(ENABLE_OVERLOADING)
metaTransformCopy_region ,
#endif
setMetaTransformCopyRegion ,
getMetaTransformCopySize ,
#if defined(ENABLE_OVERLOADING)
metaTransformCopy_size ,
#endif
setMetaTransformCopySize ,
) 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.Kind as DK
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
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
#else
#endif
newtype MetaTransformCopy = MetaTransformCopy (SP.ManagedPtr MetaTransformCopy)
deriving (MetaTransformCopy -> MetaTransformCopy -> Bool
(MetaTransformCopy -> MetaTransformCopy -> Bool)
-> (MetaTransformCopy -> MetaTransformCopy -> Bool)
-> Eq MetaTransformCopy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MetaTransformCopy -> MetaTransformCopy -> Bool
== :: MetaTransformCopy -> MetaTransformCopy -> Bool
$c/= :: MetaTransformCopy -> MetaTransformCopy -> Bool
/= :: MetaTransformCopy -> MetaTransformCopy -> Bool
Eq)
instance SP.ManagedPtrNewtype MetaTransformCopy where
toManagedPtr :: MetaTransformCopy -> ManagedPtr MetaTransformCopy
toManagedPtr (MetaTransformCopy ManagedPtr MetaTransformCopy
p) = ManagedPtr MetaTransformCopy
p
instance BoxedPtr MetaTransformCopy where
boxedPtrCopy :: MetaTransformCopy -> IO MetaTransformCopy
boxedPtrCopy = \MetaTransformCopy
p -> MetaTransformCopy
-> (Ptr MetaTransformCopy -> IO MetaTransformCopy)
-> IO MetaTransformCopy
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr MetaTransformCopy
p (Int -> Ptr MetaTransformCopy -> IO (Ptr MetaTransformCopy)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
24 (Ptr MetaTransformCopy -> IO (Ptr MetaTransformCopy))
-> (Ptr MetaTransformCopy -> IO MetaTransformCopy)
-> Ptr MetaTransformCopy
-> IO MetaTransformCopy
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr MetaTransformCopy -> MetaTransformCopy)
-> Ptr MetaTransformCopy -> IO MetaTransformCopy
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr MetaTransformCopy -> MetaTransformCopy
MetaTransformCopy)
boxedPtrFree :: MetaTransformCopy -> IO ()
boxedPtrFree = \MetaTransformCopy
x -> MetaTransformCopy -> (Ptr MetaTransformCopy -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr MetaTransformCopy
x Ptr MetaTransformCopy -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr MetaTransformCopy where
boxedPtrCalloc :: IO (Ptr MetaTransformCopy)
boxedPtrCalloc = Int -> IO (Ptr MetaTransformCopy)
forall a. Int -> IO (Ptr a)
callocBytes Int
24
newZeroMetaTransformCopy :: MonadIO m => m MetaTransformCopy
newZeroMetaTransformCopy :: forall (m :: * -> *). MonadIO m => m MetaTransformCopy
newZeroMetaTransformCopy = IO MetaTransformCopy -> m MetaTransformCopy
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MetaTransformCopy -> m MetaTransformCopy)
-> IO MetaTransformCopy -> m MetaTransformCopy
forall a b. (a -> b) -> a -> b
$ IO (Ptr MetaTransformCopy)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr MetaTransformCopy)
-> (Ptr MetaTransformCopy -> IO MetaTransformCopy)
-> IO MetaTransformCopy
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr MetaTransformCopy -> MetaTransformCopy)
-> Ptr MetaTransformCopy -> IO MetaTransformCopy
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr MetaTransformCopy -> MetaTransformCopy
MetaTransformCopy
instance tag ~ 'AttrSet => Constructible MetaTransformCopy tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr MetaTransformCopy -> MetaTransformCopy)
-> [AttrOp MetaTransformCopy tag] -> m MetaTransformCopy
new ManagedPtr MetaTransformCopy -> MetaTransformCopy
_ [AttrOp MetaTransformCopy tag]
attrs = do
MetaTransformCopy
o <- m MetaTransformCopy
forall (m :: * -> *). MonadIO m => m MetaTransformCopy
newZeroMetaTransformCopy
MetaTransformCopy -> [AttrOp MetaTransformCopy 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set MetaTransformCopy
o [AttrOp MetaTransformCopy tag]
[AttrOp MetaTransformCopy 'AttrSet]
attrs
MetaTransformCopy -> m MetaTransformCopy
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return MetaTransformCopy
o
getMetaTransformCopyRegion :: MonadIO m => MetaTransformCopy -> m Bool
getMetaTransformCopyRegion :: forall (m :: * -> *). MonadIO m => MetaTransformCopy -> m Bool
getMetaTransformCopyRegion MetaTransformCopy
s = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ MetaTransformCopy -> (Ptr MetaTransformCopy -> IO Bool) -> IO Bool
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaTransformCopy
s ((Ptr MetaTransformCopy -> IO Bool) -> IO Bool)
-> (Ptr MetaTransformCopy -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr MetaTransformCopy
ptr -> do
CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr MetaTransformCopy
ptr Ptr MetaTransformCopy -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CInt
let val' :: Bool
val' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
val
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
val'
setMetaTransformCopyRegion :: MonadIO m => MetaTransformCopy -> Bool -> m ()
setMetaTransformCopyRegion :: forall (m :: * -> *).
MonadIO m =>
MetaTransformCopy -> Bool -> m ()
setMetaTransformCopyRegion MetaTransformCopy
s Bool
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
$ MetaTransformCopy -> (Ptr MetaTransformCopy -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaTransformCopy
s ((Ptr MetaTransformCopy -> IO ()) -> IO ())
-> (Ptr MetaTransformCopy -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr MetaTransformCopy
ptr -> do
let val' :: CInt
val' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
val
Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr MetaTransformCopy
ptr Ptr MetaTransformCopy -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CInt
val' :: CInt)
#if defined(ENABLE_OVERLOADING)
data MetaTransformCopyRegionFieldInfo
instance AttrInfo MetaTransformCopyRegionFieldInfo where
type AttrBaseTypeConstraint MetaTransformCopyRegionFieldInfo = (~) MetaTransformCopy
type AttrAllowedOps MetaTransformCopyRegionFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint MetaTransformCopyRegionFieldInfo = (~) Bool
type AttrTransferTypeConstraint MetaTransformCopyRegionFieldInfo = (~)Bool
type AttrTransferType MetaTransformCopyRegionFieldInfo = Bool
type AttrGetType MetaTransformCopyRegionFieldInfo = Bool
type AttrLabel MetaTransformCopyRegionFieldInfo = "region"
type AttrOrigin MetaTransformCopyRegionFieldInfo = MetaTransformCopy
attrGet = getMetaTransformCopyRegion
attrSet = setMetaTransformCopyRegion
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Structs.MetaTransformCopy.region"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Structs-MetaTransformCopy.html#g:attr:region"
})
metaTransformCopy_region :: AttrLabelProxy "region"
metaTransformCopy_region = AttrLabelProxy
#endif
getMetaTransformCopyOffset :: MonadIO m => MetaTransformCopy -> m FCT.CSize
getMetaTransformCopyOffset :: forall (m :: * -> *). MonadIO m => MetaTransformCopy -> m CSize
getMetaTransformCopyOffset MetaTransformCopy
s = IO CSize -> m CSize
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CSize -> m CSize) -> IO CSize -> m CSize
forall a b. (a -> b) -> a -> b
$ MetaTransformCopy
-> (Ptr MetaTransformCopy -> IO CSize) -> IO CSize
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaTransformCopy
s ((Ptr MetaTransformCopy -> IO CSize) -> IO CSize)
-> (Ptr MetaTransformCopy -> IO CSize) -> IO CSize
forall a b. (a -> b) -> a -> b
$ \Ptr MetaTransformCopy
ptr -> do
CSize
val <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek (Ptr MetaTransformCopy
ptr Ptr MetaTransformCopy -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO FCT.CSize
CSize -> IO CSize
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CSize
val
setMetaTransformCopyOffset :: MonadIO m => MetaTransformCopy -> FCT.CSize -> m ()
setMetaTransformCopyOffset :: forall (m :: * -> *).
MonadIO m =>
MetaTransformCopy -> CSize -> m ()
setMetaTransformCopyOffset MetaTransformCopy
s CSize
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
$ MetaTransformCopy -> (Ptr MetaTransformCopy -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaTransformCopy
s ((Ptr MetaTransformCopy -> IO ()) -> IO ())
-> (Ptr MetaTransformCopy -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr MetaTransformCopy
ptr -> do
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr MetaTransformCopy
ptr Ptr MetaTransformCopy -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CSize
val :: FCT.CSize)
#if defined(ENABLE_OVERLOADING)
data MetaTransformCopyOffsetFieldInfo
instance AttrInfo MetaTransformCopyOffsetFieldInfo where
type AttrBaseTypeConstraint MetaTransformCopyOffsetFieldInfo = (~) MetaTransformCopy
type AttrAllowedOps MetaTransformCopyOffsetFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint MetaTransformCopyOffsetFieldInfo = (~) FCT.CSize
type AttrTransferTypeConstraint MetaTransformCopyOffsetFieldInfo = (~)FCT.CSize
type AttrTransferType MetaTransformCopyOffsetFieldInfo = FCT.CSize
type AttrGetType MetaTransformCopyOffsetFieldInfo = FCT.CSize
type AttrLabel MetaTransformCopyOffsetFieldInfo = "offset"
type AttrOrigin MetaTransformCopyOffsetFieldInfo = MetaTransformCopy
attrGet = getMetaTransformCopyOffset
attrSet = setMetaTransformCopyOffset
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Structs.MetaTransformCopy.offset"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Structs-MetaTransformCopy.html#g:attr:offset"
})
metaTransformCopy_offset :: AttrLabelProxy "offset"
metaTransformCopy_offset = AttrLabelProxy
#endif
getMetaTransformCopySize :: MonadIO m => MetaTransformCopy -> m FCT.CSize
getMetaTransformCopySize :: forall (m :: * -> *). MonadIO m => MetaTransformCopy -> m CSize
getMetaTransformCopySize MetaTransformCopy
s = IO CSize -> m CSize
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CSize -> m CSize) -> IO CSize -> m CSize
forall a b. (a -> b) -> a -> b
$ MetaTransformCopy
-> (Ptr MetaTransformCopy -> IO CSize) -> IO CSize
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaTransformCopy
s ((Ptr MetaTransformCopy -> IO CSize) -> IO CSize)
-> (Ptr MetaTransformCopy -> IO CSize) -> IO CSize
forall a b. (a -> b) -> a -> b
$ \Ptr MetaTransformCopy
ptr -> do
CSize
val <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek (Ptr MetaTransformCopy
ptr Ptr MetaTransformCopy -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO FCT.CSize
CSize -> IO CSize
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CSize
val
setMetaTransformCopySize :: MonadIO m => MetaTransformCopy -> FCT.CSize -> m ()
setMetaTransformCopySize :: forall (m :: * -> *).
MonadIO m =>
MetaTransformCopy -> CSize -> m ()
setMetaTransformCopySize MetaTransformCopy
s CSize
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
$ MetaTransformCopy -> (Ptr MetaTransformCopy -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MetaTransformCopy
s ((Ptr MetaTransformCopy -> IO ()) -> IO ())
-> (Ptr MetaTransformCopy -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr MetaTransformCopy
ptr -> do
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr MetaTransformCopy
ptr Ptr MetaTransformCopy -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (CSize
val :: FCT.CSize)
#if defined(ENABLE_OVERLOADING)
data MetaTransformCopySizeFieldInfo
instance AttrInfo MetaTransformCopySizeFieldInfo where
type AttrBaseTypeConstraint MetaTransformCopySizeFieldInfo = (~) MetaTransformCopy
type AttrAllowedOps MetaTransformCopySizeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint MetaTransformCopySizeFieldInfo = (~) FCT.CSize
type AttrTransferTypeConstraint MetaTransformCopySizeFieldInfo = (~)FCT.CSize
type AttrTransferType MetaTransformCopySizeFieldInfo = FCT.CSize
type AttrGetType MetaTransformCopySizeFieldInfo = FCT.CSize
type AttrLabel MetaTransformCopySizeFieldInfo = "size"
type AttrOrigin MetaTransformCopySizeFieldInfo = MetaTransformCopy
attrGet = getMetaTransformCopySize
attrSet = setMetaTransformCopySize
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Structs.MetaTransformCopy.size"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Structs-MetaTransformCopy.html#g:attr:size"
})
metaTransformCopy_size :: AttrLabelProxy "size"
metaTransformCopy_size = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList MetaTransformCopy
type instance O.AttributeList MetaTransformCopy = MetaTransformCopyAttributeList
type MetaTransformCopyAttributeList = ('[ '("region", MetaTransformCopyRegionFieldInfo), '("offset", MetaTransformCopyOffsetFieldInfo), '("size", MetaTransformCopySizeFieldInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveMetaTransformCopyMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveMetaTransformCopyMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveMetaTransformCopyMethod t MetaTransformCopy, O.OverloadedMethod info MetaTransformCopy p) => OL.IsLabel t (MetaTransformCopy -> 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 ~ ResolveMetaTransformCopyMethod t MetaTransformCopy, O.OverloadedMethod info MetaTransformCopy p, R.HasField t MetaTransformCopy p) => R.HasField t MetaTransformCopy p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveMetaTransformCopyMethod t MetaTransformCopy, O.OverloadedMethodInfo info MetaTransformCopy) => OL.IsLabel t (O.MethodProxy info MetaTransformCopy) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif