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

Structure describing the color info.
-}

module GI.GstVideo.Structs.VideoColorimetry
    ( 

-- * Exported types
    VideoColorimetry(..)                    ,
    newZeroVideoColorimetry                 ,
    noVideoColorimetry                      ,


 -- * Methods
-- ** fromString #method:fromString#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VideoColorimetryFromStringMethodInfo    ,
#endif
    videoColorimetryFromString              ,


-- ** isEqual #method:isEqual#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VideoColorimetryIsEqualMethodInfo       ,
#endif
    videoColorimetryIsEqual                 ,


-- ** matches #method:matches#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VideoColorimetryMatchesMethodInfo       ,
#endif
    videoColorimetryMatches                 ,


-- ** toString #method:toString#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VideoColorimetryToStringMethodInfo      ,
#endif
    videoColorimetryToString                ,




 -- * Properties
-- ** matrix #attr:matrix#
    getVideoColorimetryMatrix               ,
    setVideoColorimetryMatrix               ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    videoColorimetry_matrix                 ,
#endif


-- ** primaries #attr:primaries#
    getVideoColorimetryPrimaries            ,
    setVideoColorimetryPrimaries            ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    videoColorimetry_primaries              ,
#endif


-- ** range #attr:range#
    getVideoColorimetryRange                ,
    setVideoColorimetryRange                ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    videoColorimetry_range                  ,
#endif


-- ** transfer #attr:transfer#
    getVideoColorimetryTransfer             ,
    setVideoColorimetryTransfer             ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    videoColorimetry_transfer               ,
#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.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
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 {-# SOURCE #-} qualified GI.GstVideo.Enums as GstVideo.Enums

newtype VideoColorimetry = VideoColorimetry (ManagedPtr VideoColorimetry)
instance WrappedPtr VideoColorimetry where
    wrappedPtrCalloc = callocBytes 16
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 16 >=> wrapPtr VideoColorimetry)
    wrappedPtrFree = Just ptr_to_g_free

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

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


noVideoColorimetry :: Maybe VideoColorimetry
noVideoColorimetry = Nothing

getVideoColorimetryRange :: MonadIO m => VideoColorimetry -> m GstVideo.Enums.VideoColorRange
getVideoColorimetryRange s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

setVideoColorimetryRange :: MonadIO m => VideoColorimetry -> GstVideo.Enums.VideoColorRange -> m ()
setVideoColorimetryRange s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 0) (val' :: CUInt)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VideoColorimetryRangeFieldInfo
instance AttrInfo VideoColorimetryRangeFieldInfo where
    type AttrAllowedOps VideoColorimetryRangeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorimetryRangeFieldInfo = (~) GstVideo.Enums.VideoColorRange
    type AttrBaseTypeConstraint VideoColorimetryRangeFieldInfo = (~) VideoColorimetry
    type AttrGetType VideoColorimetryRangeFieldInfo = GstVideo.Enums.VideoColorRange
    type AttrLabel VideoColorimetryRangeFieldInfo = "range"
    type AttrOrigin VideoColorimetryRangeFieldInfo = VideoColorimetry
    attrGet _ = getVideoColorimetryRange
    attrSet _ = setVideoColorimetryRange
    attrConstruct = undefined
    attrClear _ = undefined

videoColorimetry_range :: AttrLabelProxy "range"
videoColorimetry_range = AttrLabelProxy

#endif


getVideoColorimetryMatrix :: MonadIO m => VideoColorimetry -> m GstVideo.Enums.VideoColorMatrix
getVideoColorimetryMatrix s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 4) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

setVideoColorimetryMatrix :: MonadIO m => VideoColorimetry -> GstVideo.Enums.VideoColorMatrix -> m ()
setVideoColorimetryMatrix s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 4) (val' :: CUInt)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VideoColorimetryMatrixFieldInfo
instance AttrInfo VideoColorimetryMatrixFieldInfo where
    type AttrAllowedOps VideoColorimetryMatrixFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorimetryMatrixFieldInfo = (~) GstVideo.Enums.VideoColorMatrix
    type AttrBaseTypeConstraint VideoColorimetryMatrixFieldInfo = (~) VideoColorimetry
    type AttrGetType VideoColorimetryMatrixFieldInfo = GstVideo.Enums.VideoColorMatrix
    type AttrLabel VideoColorimetryMatrixFieldInfo = "matrix"
    type AttrOrigin VideoColorimetryMatrixFieldInfo = VideoColorimetry
    attrGet _ = getVideoColorimetryMatrix
    attrSet _ = setVideoColorimetryMatrix
    attrConstruct = undefined
    attrClear _ = undefined

videoColorimetry_matrix :: AttrLabelProxy "matrix"
videoColorimetry_matrix = AttrLabelProxy

#endif


getVideoColorimetryTransfer :: MonadIO m => VideoColorimetry -> m GstVideo.Enums.VideoTransferFunction
getVideoColorimetryTransfer s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

setVideoColorimetryTransfer :: MonadIO m => VideoColorimetry -> GstVideo.Enums.VideoTransferFunction -> m ()
setVideoColorimetryTransfer s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 8) (val' :: CUInt)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VideoColorimetryTransferFieldInfo
instance AttrInfo VideoColorimetryTransferFieldInfo where
    type AttrAllowedOps VideoColorimetryTransferFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorimetryTransferFieldInfo = (~) GstVideo.Enums.VideoTransferFunction
    type AttrBaseTypeConstraint VideoColorimetryTransferFieldInfo = (~) VideoColorimetry
    type AttrGetType VideoColorimetryTransferFieldInfo = GstVideo.Enums.VideoTransferFunction
    type AttrLabel VideoColorimetryTransferFieldInfo = "transfer"
    type AttrOrigin VideoColorimetryTransferFieldInfo = VideoColorimetry
    attrGet _ = getVideoColorimetryTransfer
    attrSet _ = setVideoColorimetryTransfer
    attrConstruct = undefined
    attrClear _ = undefined

videoColorimetry_transfer :: AttrLabelProxy "transfer"
videoColorimetry_transfer = AttrLabelProxy

#endif


getVideoColorimetryPrimaries :: MonadIO m => VideoColorimetry -> m GstVideo.Enums.VideoColorPrimaries
getVideoColorimetryPrimaries s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 12) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

setVideoColorimetryPrimaries :: MonadIO m => VideoColorimetry -> GstVideo.Enums.VideoColorPrimaries -> m ()
setVideoColorimetryPrimaries s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 12) (val' :: CUInt)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VideoColorimetryPrimariesFieldInfo
instance AttrInfo VideoColorimetryPrimariesFieldInfo where
    type AttrAllowedOps VideoColorimetryPrimariesFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint VideoColorimetryPrimariesFieldInfo = (~) GstVideo.Enums.VideoColorPrimaries
    type AttrBaseTypeConstraint VideoColorimetryPrimariesFieldInfo = (~) VideoColorimetry
    type AttrGetType VideoColorimetryPrimariesFieldInfo = GstVideo.Enums.VideoColorPrimaries
    type AttrLabel VideoColorimetryPrimariesFieldInfo = "primaries"
    type AttrOrigin VideoColorimetryPrimariesFieldInfo = VideoColorimetry
    attrGet _ = getVideoColorimetryPrimaries
    attrSet _ = setVideoColorimetryPrimaries
    attrConstruct = undefined
    attrClear _ = undefined

videoColorimetry_primaries :: AttrLabelProxy "primaries"
videoColorimetry_primaries = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
instance O.HasAttributeList VideoColorimetry
type instance O.AttributeList VideoColorimetry = VideoColorimetryAttributeList
type VideoColorimetryAttributeList = ('[ '("range", VideoColorimetryRangeFieldInfo), '("matrix", VideoColorimetryMatrixFieldInfo), '("transfer", VideoColorimetryTransferFieldInfo), '("primaries", VideoColorimetryPrimariesFieldInfo)] :: [(Symbol, *)])
#endif

-- method VideoColorimetry::from_string
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "cinfo", argType = TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstVideoColorimetry", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "color", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a colorimetry string", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_colorimetry_from_string" gst_video_colorimetry_from_string :: 
    Ptr VideoColorimetry ->                 -- cinfo : TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"})
    CString ->                              -- color : TBasicType TUTF8
    IO CInt

{- |
Parse the colorimetry string and update /@cinfo@/ with the parsed
values.
-}
videoColorimetryFromString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoColorimetry
    {- ^ /@cinfo@/: a 'GI.GstVideo.Structs.VideoColorimetry.VideoColorimetry' -}
    -> T.Text
    {- ^ /@color@/: a colorimetry string -}
    -> m Bool
    {- ^ __Returns:__ @/TRUE/@ if /@color@/ points to valid colorimetry info. -}
videoColorimetryFromString cinfo color = liftIO $ do
    cinfo' <- unsafeManagedPtrGetPtr cinfo
    color' <- textToCString color
    result <- gst_video_colorimetry_from_string cinfo' color'
    let result' = (/= 0) result
    touchManagedPtr cinfo
    freeMem color'
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VideoColorimetryFromStringMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.MethodInfo VideoColorimetryFromStringMethodInfo VideoColorimetry signature where
    overloadedMethod _ = videoColorimetryFromString

#endif

-- method VideoColorimetry::is_equal
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "cinfo", argType = TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstVideoColorimetry", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "other", argType = TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "another #GstVideoColorimetry", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_colorimetry_is_equal" gst_video_colorimetry_is_equal :: 
    Ptr VideoColorimetry ->                 -- cinfo : TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"})
    Ptr VideoColorimetry ->                 -- other : TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"})
    IO CInt

{- |
Compare the 2 colorimetry sets for equality

@since 1.6
-}
videoColorimetryIsEqual ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoColorimetry
    {- ^ /@cinfo@/: a 'GI.GstVideo.Structs.VideoColorimetry.VideoColorimetry' -}
    -> VideoColorimetry
    {- ^ /@other@/: another 'GI.GstVideo.Structs.VideoColorimetry.VideoColorimetry' -}
    -> m Bool
    {- ^ __Returns:__ @/TRUE/@ if /@cinfo@/ and /@other@/ are equal. -}
videoColorimetryIsEqual cinfo other = liftIO $ do
    cinfo' <- unsafeManagedPtrGetPtr cinfo
    other' <- unsafeManagedPtrGetPtr other
    result <- gst_video_colorimetry_is_equal cinfo' other'
    let result' = (/= 0) result
    touchManagedPtr cinfo
    touchManagedPtr other
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VideoColorimetryIsEqualMethodInfo
instance (signature ~ (VideoColorimetry -> m Bool), MonadIO m) => O.MethodInfo VideoColorimetryIsEqualMethodInfo VideoColorimetry signature where
    overloadedMethod _ = videoColorimetryIsEqual

#endif

-- method VideoColorimetry::matches
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "cinfo", argType = TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstVideoInfo", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "color", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a colorimetry string", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_colorimetry_matches" gst_video_colorimetry_matches :: 
    Ptr VideoColorimetry ->                 -- cinfo : TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"})
    CString ->                              -- color : TBasicType TUTF8
    IO CInt

{- |
Check if the colorimetry information in /@info@/ matches that of the
string /@color@/.
-}
videoColorimetryMatches ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoColorimetry
    {- ^ /@cinfo@/: a 'GI.GstVideo.Structs.VideoInfo.VideoInfo' -}
    -> T.Text
    {- ^ /@color@/: a colorimetry string -}
    -> m Bool
    {- ^ __Returns:__ @/TRUE/@ if /@color@/ conveys the same colorimetry info as the color
information in /@info@/. -}
videoColorimetryMatches cinfo color = liftIO $ do
    cinfo' <- unsafeManagedPtrGetPtr cinfo
    color' <- textToCString color
    result <- gst_video_colorimetry_matches cinfo' color'
    let result' = (/= 0) result
    touchManagedPtr cinfo
    freeMem color'
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VideoColorimetryMatchesMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.MethodInfo VideoColorimetryMatchesMethodInfo VideoColorimetry signature where
    overloadedMethod _ = videoColorimetryMatches

#endif

-- method VideoColorimetry::to_string
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "cinfo", argType = TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstVideoColorimetry", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_colorimetry_to_string" gst_video_colorimetry_to_string :: 
    Ptr VideoColorimetry ->                 -- cinfo : TInterface (Name {namespace = "GstVideo", name = "VideoColorimetry"})
    IO CString

{- |
Make a string representation of /@cinfo@/.
-}
videoColorimetryToString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoColorimetry
    {- ^ /@cinfo@/: a 'GI.GstVideo.Structs.VideoColorimetry.VideoColorimetry' -}
    -> m T.Text
    {- ^ __Returns:__ a string representation of /@cinfo@/. -}
videoColorimetryToString cinfo = liftIO $ do
    cinfo' <- unsafeManagedPtrGetPtr cinfo
    result <- gst_video_colorimetry_to_string cinfo'
    checkUnexpectedReturnNULL "videoColorimetryToString" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr cinfo
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VideoColorimetryToStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo VideoColorimetryToStringMethodInfo VideoColorimetry signature where
    overloadedMethod _ = videoColorimetryToString

#endif

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
type family ResolveVideoColorimetryMethod (t :: Symbol) (o :: *) :: * where
    ResolveVideoColorimetryMethod "fromString" o = VideoColorimetryFromStringMethodInfo
    ResolveVideoColorimetryMethod "isEqual" o = VideoColorimetryIsEqualMethodInfo
    ResolveVideoColorimetryMethod "matches" o = VideoColorimetryMatchesMethodInfo
    ResolveVideoColorimetryMethod "toString" o = VideoColorimetryToStringMethodInfo
    ResolveVideoColorimetryMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveVideoColorimetryMethod t VideoColorimetry, O.MethodInfo info VideoColorimetry p) => O.IsLabelProxy t (VideoColorimetry -> p) where
    fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)

#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveVideoColorimetryMethod t VideoColorimetry, O.MethodInfo info VideoColorimetry p) => O.IsLabel t (VideoColorimetry -> 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

#endif