{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Structure describing the chromaticity coordinates of an RGB system. These
-- values can be used to construct a matrix to transform RGB to and from the
-- XYZ colorspace.
-- 
-- /Since: 1.6/

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

module GI.GstVideo.Structs.VideoColorPrimariesInfo
    ( 

-- * Exported types
    VideoColorPrimariesInfo(..)             ,
    newZeroVideoColorPrimariesInfo          ,
    noVideoColorPrimariesInfo               ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveVideoColorPrimariesInfoMethod    ,
#endif




 -- * Properties
-- ** bx #attr:bx#
-- | blue x coordinate

    getVideoColorPrimariesInfoBx            ,
    setVideoColorPrimariesInfoBx            ,
#if defined(ENABLE_OVERLOADING)
    videoColorPrimariesInfo_bx              ,
#endif


-- ** by #attr:by#
-- | blue y coordinate

    getVideoColorPrimariesInfoBy            ,
    setVideoColorPrimariesInfoBy            ,
#if defined(ENABLE_OVERLOADING)
    videoColorPrimariesInfo_by              ,
#endif


-- ** gx #attr:gx#
-- | green x coordinate

    getVideoColorPrimariesInfoGx            ,
    setVideoColorPrimariesInfoGx            ,
#if defined(ENABLE_OVERLOADING)
    videoColorPrimariesInfo_gx              ,
#endif


-- ** gy #attr:gy#
-- | green y coordinate

    getVideoColorPrimariesInfoGy            ,
    setVideoColorPrimariesInfoGy            ,
#if defined(ENABLE_OVERLOADING)
    videoColorPrimariesInfo_gy              ,
#endif


-- ** primaries #attr:primaries#
-- | a t'GI.GstVideo.Enums.VideoColorPrimaries'

    getVideoColorPrimariesInfoPrimaries     ,
    setVideoColorPrimariesInfoPrimaries     ,
#if defined(ENABLE_OVERLOADING)
    videoColorPrimariesInfo_primaries       ,
#endif


-- ** rx #attr:rx#
-- | red x coordinate

    getVideoColorPrimariesInfoRx            ,
    setVideoColorPrimariesInfoRx            ,
#if defined(ENABLE_OVERLOADING)
    videoColorPrimariesInfo_rx              ,
#endif


-- ** ry #attr:ry#
-- | red y coordinate

    getVideoColorPrimariesInfoRy            ,
    setVideoColorPrimariesInfoRy            ,
#if defined(ENABLE_OVERLOADING)
    videoColorPrimariesInfo_ry              ,
#endif


-- ** wx #attr:wx#
-- | reference white x coordinate

    getVideoColorPrimariesInfoWx            ,
    setVideoColorPrimariesInfoWx            ,
#if defined(ENABLE_OVERLOADING)
    videoColorPrimariesInfo_wx              ,
#endif


-- ** wy #attr:wy#
-- | reference white y coordinate

    getVideoColorPrimariesInfoWy            ,
    setVideoColorPrimariesInfoWy            ,
#if defined(ENABLE_OVERLOADING)
    videoColorPrimariesInfo_wy              ,
#endif




    ) 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 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 {-# SOURCE #-} qualified GI.GstVideo.Enums as GstVideo.Enums

-- | Memory-managed wrapper type.
newtype VideoColorPrimariesInfo = VideoColorPrimariesInfo (ManagedPtr VideoColorPrimariesInfo)
    deriving (VideoColorPrimariesInfo -> VideoColorPrimariesInfo -> Bool
(VideoColorPrimariesInfo -> VideoColorPrimariesInfo -> Bool)
-> (VideoColorPrimariesInfo -> VideoColorPrimariesInfo -> Bool)
-> Eq VideoColorPrimariesInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VideoColorPrimariesInfo -> VideoColorPrimariesInfo -> Bool
$c/= :: VideoColorPrimariesInfo -> VideoColorPrimariesInfo -> Bool
== :: VideoColorPrimariesInfo -> VideoColorPrimariesInfo -> Bool
$c== :: VideoColorPrimariesInfo -> VideoColorPrimariesInfo -> Bool
Eq)
instance WrappedPtr VideoColorPrimariesInfo where
    wrappedPtrCalloc :: IO (Ptr VideoColorPrimariesInfo)
wrappedPtrCalloc = Int -> IO (Ptr VideoColorPrimariesInfo)
forall a. Int -> IO (Ptr a)
callocBytes 72
    wrappedPtrCopy :: VideoColorPrimariesInfo -> IO VideoColorPrimariesInfo
wrappedPtrCopy = \p :: VideoColorPrimariesInfo
p -> VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO VideoColorPrimariesInfo)
-> IO VideoColorPrimariesInfo
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
p (Int
-> Ptr VideoColorPrimariesInfo -> IO (Ptr VideoColorPrimariesInfo)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 72 (Ptr VideoColorPrimariesInfo -> IO (Ptr VideoColorPrimariesInfo))
-> (Ptr VideoColorPrimariesInfo -> IO VideoColorPrimariesInfo)
-> Ptr VideoColorPrimariesInfo
-> IO VideoColorPrimariesInfo
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr VideoColorPrimariesInfo -> VideoColorPrimariesInfo)
-> Ptr VideoColorPrimariesInfo -> IO VideoColorPrimariesInfo
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr VideoColorPrimariesInfo -> VideoColorPrimariesInfo
VideoColorPrimariesInfo)
    wrappedPtrFree :: Maybe (GDestroyNotify VideoColorPrimariesInfo)
wrappedPtrFree = GDestroyNotify VideoColorPrimariesInfo
-> Maybe (GDestroyNotify VideoColorPrimariesInfo)
forall a. a -> Maybe a
Just GDestroyNotify VideoColorPrimariesInfo
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `VideoColorPrimariesInfo`.
noVideoColorPrimariesInfo :: Maybe VideoColorPrimariesInfo
noVideoColorPrimariesInfo :: Maybe VideoColorPrimariesInfo
noVideoColorPrimariesInfo = Maybe VideoColorPrimariesInfo
forall a. Maybe a
Nothing

-- | Get the value of the “@primaries@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' videoColorPrimariesInfo #primaries
-- @
getVideoColorPrimariesInfoPrimaries :: MonadIO m => VideoColorPrimariesInfo -> m GstVideo.Enums.VideoColorPrimaries
getVideoColorPrimariesInfoPrimaries :: VideoColorPrimariesInfo -> m VideoColorPrimaries
getVideoColorPrimariesInfoPrimaries s :: VideoColorPrimariesInfo
s = IO VideoColorPrimaries -> m VideoColorPrimaries
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO VideoColorPrimaries -> m VideoColorPrimaries)
-> IO VideoColorPrimaries -> m VideoColorPrimaries
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO VideoColorPrimaries)
-> IO VideoColorPrimaries
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO VideoColorPrimaries)
 -> IO VideoColorPrimaries)
-> (Ptr VideoColorPrimariesInfo -> IO VideoColorPrimaries)
-> IO VideoColorPrimaries
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO CUInt
    let val' :: VideoColorPrimaries
val' = (Int -> VideoColorPrimaries
forall a. Enum a => Int -> a
toEnum (Int -> VideoColorPrimaries)
-> (CUInt -> Int) -> CUInt -> VideoColorPrimaries
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
val
    VideoColorPrimaries -> IO VideoColorPrimaries
forall (m :: * -> *) a. Monad m => a -> m a
return VideoColorPrimaries
val'

-- | Set the value of the “@primaries@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' videoColorPrimariesInfo [ #primaries 'Data.GI.Base.Attributes.:=' value ]
-- @
setVideoColorPrimariesInfoPrimaries :: MonadIO m => VideoColorPrimariesInfo -> GstVideo.Enums.VideoColorPrimaries -> m ()
setVideoColorPrimariesInfoPrimaries :: VideoColorPrimariesInfo -> VideoColorPrimaries -> m ()
setVideoColorPrimariesInfoPrimaries s :: VideoColorPrimariesInfo
s val :: VideoColorPrimaries
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO ()) -> IO ())
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    let val' :: CUInt
val' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (VideoColorPrimaries -> Int) -> VideoColorPrimaries -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VideoColorPrimaries -> Int
forall a. Enum a => a -> Int
fromEnum) VideoColorPrimaries
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (CUInt
val' :: CUInt)

#if defined(ENABLE_OVERLOADING)
data VideoColorPrimariesInfoPrimariesFieldInfo
instance AttrInfo VideoColorPrimariesInfoPrimariesFieldInfo where
    type AttrBaseTypeConstraint VideoColorPrimariesInfoPrimariesFieldInfo = (~) VideoColorPrimariesInfo
    type AttrAllowedOps VideoColorPrimariesInfoPrimariesFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorPrimariesInfoPrimariesFieldInfo = (~) GstVideo.Enums.VideoColorPrimaries
    type AttrTransferTypeConstraint VideoColorPrimariesInfoPrimariesFieldInfo = (~)GstVideo.Enums.VideoColorPrimaries
    type AttrTransferType VideoColorPrimariesInfoPrimariesFieldInfo = GstVideo.Enums.VideoColorPrimaries
    type AttrGetType VideoColorPrimariesInfoPrimariesFieldInfo = GstVideo.Enums.VideoColorPrimaries
    type AttrLabel VideoColorPrimariesInfoPrimariesFieldInfo = "primaries"
    type AttrOrigin VideoColorPrimariesInfoPrimariesFieldInfo = VideoColorPrimariesInfo
    attrGet = getVideoColorPrimariesInfoPrimaries
    attrSet = setVideoColorPrimariesInfoPrimaries
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

videoColorPrimariesInfo_primaries :: AttrLabelProxy "primaries"
videoColorPrimariesInfo_primaries = AttrLabelProxy

#endif


-- | Get the value of the “@Wx@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' videoColorPrimariesInfo #wx
-- @
getVideoColorPrimariesInfoWx :: MonadIO m => VideoColorPrimariesInfo -> m Double
getVideoColorPrimariesInfoWx :: VideoColorPrimariesInfo -> m Double
getVideoColorPrimariesInfoWx s :: VideoColorPrimariesInfo
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double)
-> (Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'

-- | Set the value of the “@Wx@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' videoColorPrimariesInfo [ #wx 'Data.GI.Base.Attributes.:=' value ]
-- @
setVideoColorPrimariesInfoWx :: MonadIO m => VideoColorPrimariesInfo -> Double -> m ()
setVideoColorPrimariesInfoWx :: VideoColorPrimariesInfo -> Double -> m ()
setVideoColorPrimariesInfoWx s :: VideoColorPrimariesInfo
s val :: Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO ()) -> IO ())
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data VideoColorPrimariesInfoWxFieldInfo
instance AttrInfo VideoColorPrimariesInfoWxFieldInfo where
    type AttrBaseTypeConstraint VideoColorPrimariesInfoWxFieldInfo = (~) VideoColorPrimariesInfo
    type AttrAllowedOps VideoColorPrimariesInfoWxFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorPrimariesInfoWxFieldInfo = (~) Double
    type AttrTransferTypeConstraint VideoColorPrimariesInfoWxFieldInfo = (~)Double
    type AttrTransferType VideoColorPrimariesInfoWxFieldInfo = Double
    type AttrGetType VideoColorPrimariesInfoWxFieldInfo = Double
    type AttrLabel VideoColorPrimariesInfoWxFieldInfo = "Wx"
    type AttrOrigin VideoColorPrimariesInfoWxFieldInfo = VideoColorPrimariesInfo
    attrGet = getVideoColorPrimariesInfoWx
    attrSet = setVideoColorPrimariesInfoWx
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

videoColorPrimariesInfo_wx :: AttrLabelProxy "wx"
videoColorPrimariesInfo_wx = AttrLabelProxy

#endif


-- | Get the value of the “@Wy@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' videoColorPrimariesInfo #wy
-- @
getVideoColorPrimariesInfoWy :: MonadIO m => VideoColorPrimariesInfo -> m Double
getVideoColorPrimariesInfoWy :: VideoColorPrimariesInfo -> m Double
getVideoColorPrimariesInfoWy s :: VideoColorPrimariesInfo
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double)
-> (Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'

-- | Set the value of the “@Wy@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' videoColorPrimariesInfo [ #wy 'Data.GI.Base.Attributes.:=' value ]
-- @
setVideoColorPrimariesInfoWy :: MonadIO m => VideoColorPrimariesInfo -> Double -> m ()
setVideoColorPrimariesInfoWy :: VideoColorPrimariesInfo -> Double -> m ()
setVideoColorPrimariesInfoWy s :: VideoColorPrimariesInfo
s val :: Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO ()) -> IO ())
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data VideoColorPrimariesInfoWyFieldInfo
instance AttrInfo VideoColorPrimariesInfoWyFieldInfo where
    type AttrBaseTypeConstraint VideoColorPrimariesInfoWyFieldInfo = (~) VideoColorPrimariesInfo
    type AttrAllowedOps VideoColorPrimariesInfoWyFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorPrimariesInfoWyFieldInfo = (~) Double
    type AttrTransferTypeConstraint VideoColorPrimariesInfoWyFieldInfo = (~)Double
    type AttrTransferType VideoColorPrimariesInfoWyFieldInfo = Double
    type AttrGetType VideoColorPrimariesInfoWyFieldInfo = Double
    type AttrLabel VideoColorPrimariesInfoWyFieldInfo = "Wy"
    type AttrOrigin VideoColorPrimariesInfoWyFieldInfo = VideoColorPrimariesInfo
    attrGet = getVideoColorPrimariesInfoWy
    attrSet = setVideoColorPrimariesInfoWy
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

videoColorPrimariesInfo_wy :: AttrLabelProxy "wy"
videoColorPrimariesInfo_wy = AttrLabelProxy

#endif


-- | Get the value of the “@Rx@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' videoColorPrimariesInfo #rx
-- @
getVideoColorPrimariesInfoRx :: MonadIO m => VideoColorPrimariesInfo -> m Double
getVideoColorPrimariesInfoRx :: VideoColorPrimariesInfo -> m Double
getVideoColorPrimariesInfoRx s :: VideoColorPrimariesInfo
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double)
-> (Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'

-- | Set the value of the “@Rx@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' videoColorPrimariesInfo [ #rx 'Data.GI.Base.Attributes.:=' value ]
-- @
setVideoColorPrimariesInfoRx :: MonadIO m => VideoColorPrimariesInfo -> Double -> m ()
setVideoColorPrimariesInfoRx :: VideoColorPrimariesInfo -> Double -> m ()
setVideoColorPrimariesInfoRx s :: VideoColorPrimariesInfo
s val :: Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO ()) -> IO ())
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data VideoColorPrimariesInfoRxFieldInfo
instance AttrInfo VideoColorPrimariesInfoRxFieldInfo where
    type AttrBaseTypeConstraint VideoColorPrimariesInfoRxFieldInfo = (~) VideoColorPrimariesInfo
    type AttrAllowedOps VideoColorPrimariesInfoRxFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorPrimariesInfoRxFieldInfo = (~) Double
    type AttrTransferTypeConstraint VideoColorPrimariesInfoRxFieldInfo = (~)Double
    type AttrTransferType VideoColorPrimariesInfoRxFieldInfo = Double
    type AttrGetType VideoColorPrimariesInfoRxFieldInfo = Double
    type AttrLabel VideoColorPrimariesInfoRxFieldInfo = "Rx"
    type AttrOrigin VideoColorPrimariesInfoRxFieldInfo = VideoColorPrimariesInfo
    attrGet = getVideoColorPrimariesInfoRx
    attrSet = setVideoColorPrimariesInfoRx
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

videoColorPrimariesInfo_rx :: AttrLabelProxy "rx"
videoColorPrimariesInfo_rx = AttrLabelProxy

#endif


-- | Get the value of the “@Ry@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' videoColorPrimariesInfo #ry
-- @
getVideoColorPrimariesInfoRy :: MonadIO m => VideoColorPrimariesInfo -> m Double
getVideoColorPrimariesInfoRy :: VideoColorPrimariesInfo -> m Double
getVideoColorPrimariesInfoRy s :: VideoColorPrimariesInfo
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double)
-> (Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'

-- | Set the value of the “@Ry@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' videoColorPrimariesInfo [ #ry 'Data.GI.Base.Attributes.:=' value ]
-- @
setVideoColorPrimariesInfoRy :: MonadIO m => VideoColorPrimariesInfo -> Double -> m ()
setVideoColorPrimariesInfoRy :: VideoColorPrimariesInfo -> Double -> m ()
setVideoColorPrimariesInfoRy s :: VideoColorPrimariesInfo
s val :: Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO ()) -> IO ())
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data VideoColorPrimariesInfoRyFieldInfo
instance AttrInfo VideoColorPrimariesInfoRyFieldInfo where
    type AttrBaseTypeConstraint VideoColorPrimariesInfoRyFieldInfo = (~) VideoColorPrimariesInfo
    type AttrAllowedOps VideoColorPrimariesInfoRyFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorPrimariesInfoRyFieldInfo = (~) Double
    type AttrTransferTypeConstraint VideoColorPrimariesInfoRyFieldInfo = (~)Double
    type AttrTransferType VideoColorPrimariesInfoRyFieldInfo = Double
    type AttrGetType VideoColorPrimariesInfoRyFieldInfo = Double
    type AttrLabel VideoColorPrimariesInfoRyFieldInfo = "Ry"
    type AttrOrigin VideoColorPrimariesInfoRyFieldInfo = VideoColorPrimariesInfo
    attrGet = getVideoColorPrimariesInfoRy
    attrSet = setVideoColorPrimariesInfoRy
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

videoColorPrimariesInfo_ry :: AttrLabelProxy "ry"
videoColorPrimariesInfo_ry = AttrLabelProxy

#endif


-- | Get the value of the “@Gx@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' videoColorPrimariesInfo #gx
-- @
getVideoColorPrimariesInfoGx :: MonadIO m => VideoColorPrimariesInfo -> m Double
getVideoColorPrimariesInfoGx :: VideoColorPrimariesInfo -> m Double
getVideoColorPrimariesInfoGx s :: VideoColorPrimariesInfo
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double)
-> (Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'

-- | Set the value of the “@Gx@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' videoColorPrimariesInfo [ #gx 'Data.GI.Base.Attributes.:=' value ]
-- @
setVideoColorPrimariesInfoGx :: MonadIO m => VideoColorPrimariesInfo -> Double -> m ()
setVideoColorPrimariesInfoGx :: VideoColorPrimariesInfo -> Double -> m ()
setVideoColorPrimariesInfoGx s :: VideoColorPrimariesInfo
s val :: Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO ()) -> IO ())
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data VideoColorPrimariesInfoGxFieldInfo
instance AttrInfo VideoColorPrimariesInfoGxFieldInfo where
    type AttrBaseTypeConstraint VideoColorPrimariesInfoGxFieldInfo = (~) VideoColorPrimariesInfo
    type AttrAllowedOps VideoColorPrimariesInfoGxFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorPrimariesInfoGxFieldInfo = (~) Double
    type AttrTransferTypeConstraint VideoColorPrimariesInfoGxFieldInfo = (~)Double
    type AttrTransferType VideoColorPrimariesInfoGxFieldInfo = Double
    type AttrGetType VideoColorPrimariesInfoGxFieldInfo = Double
    type AttrLabel VideoColorPrimariesInfoGxFieldInfo = "Gx"
    type AttrOrigin VideoColorPrimariesInfoGxFieldInfo = VideoColorPrimariesInfo
    attrGet = getVideoColorPrimariesInfoGx
    attrSet = setVideoColorPrimariesInfoGx
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

videoColorPrimariesInfo_gx :: AttrLabelProxy "gx"
videoColorPrimariesInfo_gx = AttrLabelProxy

#endif


-- | Get the value of the “@Gy@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' videoColorPrimariesInfo #gy
-- @
getVideoColorPrimariesInfoGy :: MonadIO m => VideoColorPrimariesInfo -> m Double
getVideoColorPrimariesInfoGy :: VideoColorPrimariesInfo -> m Double
getVideoColorPrimariesInfoGy s :: VideoColorPrimariesInfo
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double)
-> (Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'

-- | Set the value of the “@Gy@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' videoColorPrimariesInfo [ #gy 'Data.GI.Base.Attributes.:=' value ]
-- @
setVideoColorPrimariesInfoGy :: MonadIO m => VideoColorPrimariesInfo -> Double -> m ()
setVideoColorPrimariesInfoGy :: VideoColorPrimariesInfo -> Double -> m ()
setVideoColorPrimariesInfoGy s :: VideoColorPrimariesInfo
s val :: Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO ()) -> IO ())
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data VideoColorPrimariesInfoGyFieldInfo
instance AttrInfo VideoColorPrimariesInfoGyFieldInfo where
    type AttrBaseTypeConstraint VideoColorPrimariesInfoGyFieldInfo = (~) VideoColorPrimariesInfo
    type AttrAllowedOps VideoColorPrimariesInfoGyFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorPrimariesInfoGyFieldInfo = (~) Double
    type AttrTransferTypeConstraint VideoColorPrimariesInfoGyFieldInfo = (~)Double
    type AttrTransferType VideoColorPrimariesInfoGyFieldInfo = Double
    type AttrGetType VideoColorPrimariesInfoGyFieldInfo = Double
    type AttrLabel VideoColorPrimariesInfoGyFieldInfo = "Gy"
    type AttrOrigin VideoColorPrimariesInfoGyFieldInfo = VideoColorPrimariesInfo
    attrGet = getVideoColorPrimariesInfoGy
    attrSet = setVideoColorPrimariesInfoGy
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

videoColorPrimariesInfo_gy :: AttrLabelProxy "gy"
videoColorPrimariesInfo_gy = AttrLabelProxy

#endif


-- | Get the value of the “@Bx@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' videoColorPrimariesInfo #bx
-- @
getVideoColorPrimariesInfoBx :: MonadIO m => VideoColorPrimariesInfo -> m Double
getVideoColorPrimariesInfoBx :: VideoColorPrimariesInfo -> m Double
getVideoColorPrimariesInfoBx s :: VideoColorPrimariesInfo
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double)
-> (Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'

-- | Set the value of the “@Bx@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' videoColorPrimariesInfo [ #bx 'Data.GI.Base.Attributes.:=' value ]
-- @
setVideoColorPrimariesInfoBx :: MonadIO m => VideoColorPrimariesInfo -> Double -> m ()
setVideoColorPrimariesInfoBx :: VideoColorPrimariesInfo -> Double -> m ()
setVideoColorPrimariesInfoBx s :: VideoColorPrimariesInfo
s val :: Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO ()) -> IO ())
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data VideoColorPrimariesInfoBxFieldInfo
instance AttrInfo VideoColorPrimariesInfoBxFieldInfo where
    type AttrBaseTypeConstraint VideoColorPrimariesInfoBxFieldInfo = (~) VideoColorPrimariesInfo
    type AttrAllowedOps VideoColorPrimariesInfoBxFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorPrimariesInfoBxFieldInfo = (~) Double
    type AttrTransferTypeConstraint VideoColorPrimariesInfoBxFieldInfo = (~)Double
    type AttrTransferType VideoColorPrimariesInfoBxFieldInfo = Double
    type AttrGetType VideoColorPrimariesInfoBxFieldInfo = Double
    type AttrLabel VideoColorPrimariesInfoBxFieldInfo = "Bx"
    type AttrOrigin VideoColorPrimariesInfoBxFieldInfo = VideoColorPrimariesInfo
    attrGet = getVideoColorPrimariesInfoBx
    attrSet = setVideoColorPrimariesInfoBx
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

videoColorPrimariesInfo_bx :: AttrLabelProxy "bx"
videoColorPrimariesInfo_bx = AttrLabelProxy

#endif


-- | Get the value of the “@By@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' videoColorPrimariesInfo #by
-- @
getVideoColorPrimariesInfoBy :: MonadIO m => VideoColorPrimariesInfo -> m Double
getVideoColorPrimariesInfoBy :: VideoColorPrimariesInfo -> m Double
getVideoColorPrimariesInfoBy s :: VideoColorPrimariesInfo
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double)
-> (Ptr VideoColorPrimariesInfo -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'

-- | Set the value of the “@By@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' videoColorPrimariesInfo [ #by 'Data.GI.Base.Attributes.:=' value ]
-- @
setVideoColorPrimariesInfoBy :: MonadIO m => VideoColorPrimariesInfo -> Double -> m ()
setVideoColorPrimariesInfoBy :: VideoColorPrimariesInfo -> Double -> m ()
setVideoColorPrimariesInfoBy s :: VideoColorPrimariesInfo
s val :: Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ VideoColorPrimariesInfo
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr VideoColorPrimariesInfo
s ((Ptr VideoColorPrimariesInfo -> IO ()) -> IO ())
-> (Ptr VideoColorPrimariesInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr VideoColorPrimariesInfo
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr VideoColorPrimariesInfo
ptr Ptr VideoColorPrimariesInfo -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data VideoColorPrimariesInfoByFieldInfo
instance AttrInfo VideoColorPrimariesInfoByFieldInfo where
    type AttrBaseTypeConstraint VideoColorPrimariesInfoByFieldInfo = (~) VideoColorPrimariesInfo
    type AttrAllowedOps VideoColorPrimariesInfoByFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorPrimariesInfoByFieldInfo = (~) Double
    type AttrTransferTypeConstraint VideoColorPrimariesInfoByFieldInfo = (~)Double
    type AttrTransferType VideoColorPrimariesInfoByFieldInfo = Double
    type AttrGetType VideoColorPrimariesInfoByFieldInfo = Double
    type AttrLabel VideoColorPrimariesInfoByFieldInfo = "By"
    type AttrOrigin VideoColorPrimariesInfoByFieldInfo = VideoColorPrimariesInfo
    attrGet = getVideoColorPrimariesInfoBy
    attrSet = setVideoColorPrimariesInfoBy
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

videoColorPrimariesInfo_by :: AttrLabelProxy "by"
videoColorPrimariesInfo_by = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList VideoColorPrimariesInfo
type instance O.AttributeList VideoColorPrimariesInfo = VideoColorPrimariesInfoAttributeList
type VideoColorPrimariesInfoAttributeList = ('[ '("primaries", VideoColorPrimariesInfoPrimariesFieldInfo), '("wx", VideoColorPrimariesInfoWxFieldInfo), '("wy", VideoColorPrimariesInfoWyFieldInfo), '("rx", VideoColorPrimariesInfoRxFieldInfo), '("ry", VideoColorPrimariesInfoRyFieldInfo), '("gx", VideoColorPrimariesInfoGxFieldInfo), '("gy", VideoColorPrimariesInfoGyFieldInfo), '("bx", VideoColorPrimariesInfoBxFieldInfo), '("by", VideoColorPrimariesInfoByFieldInfo)] :: [(Symbol, *)])
#endif

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

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

#endif