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

Extra buffer metadata for performing an affine transformation using a 4x4
matrix. The transformation matrix can be composed with
'GI.GstVideo.Structs.VideoAffineTransformationMeta.videoAffineTransformationMetaApplyMatrix'.

The vertices operated on are all in the range 0 to 1, not in
Normalized Device Coordinates (-1 to +1). Transforming points in this space
are assumed to have an origin at (0.5, 0.5, 0.5) in a left-handed coordinate
system with the x-axis moving horizontally (positive values to the right),
the y-axis moving vertically (positive values up the screen) and the z-axis
perpendicular to the screen (positive values into the screen).

/Since: 1.8/
-}

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

module GI.GstVideo.Structs.VideoAffineTransformationMeta
    (

-- * Exported types
    VideoAffineTransformationMeta(..)       ,
    newZeroVideoAffineTransformationMeta    ,
    noVideoAffineTransformationMeta         ,


 -- * Methods
-- ** applyMatrix #method:applyMatrix#

#if ENABLE_OVERLOADING
    VideoAffineTransformationMetaApplyMatrixMethodInfo,
#endif
    videoAffineTransformationMetaApplyMatrix,


-- ** getInfo #method:getInfo#

    videoAffineTransformationMetaGetInfo    ,




 -- * Properties
-- ** meta #attr:meta#
{- | parent 'GI.Gst.Structs.Meta.Meta'
-}
    getVideoAffineTransformationMetaMeta    ,
#if ENABLE_OVERLOADING
    videoAffineTransformationMeta_meta      ,
#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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.Gst.Structs.Meta as Gst.Meta
import qualified GI.Gst.Structs.MetaInfo as Gst.MetaInfo

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `VideoAffineTransformationMeta`.
noVideoAffineTransformationMeta :: Maybe VideoAffineTransformationMeta
noVideoAffineTransformationMeta = Nothing

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

@
'Data.GI.Base.Attributes.get' videoAffineTransformationMeta #meta
@
-}
getVideoAffineTransformationMetaMeta :: MonadIO m => VideoAffineTransformationMeta -> m Gst.Meta.Meta
getVideoAffineTransformationMetaMeta s = liftIO $ withManagedPtr s $ \ptr -> do
    let val = ptr `plusPtr` 0 :: (Ptr Gst.Meta.Meta)
    val' <- (newPtr Gst.Meta.Meta) val
    return val'

#if ENABLE_OVERLOADING
data VideoAffineTransformationMetaMetaFieldInfo
instance AttrInfo VideoAffineTransformationMetaMetaFieldInfo where
    type AttrAllowedOps VideoAffineTransformationMetaMetaFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint VideoAffineTransformationMetaMetaFieldInfo = (~) (Ptr Gst.Meta.Meta)
    type AttrBaseTypeConstraint VideoAffineTransformationMetaMetaFieldInfo = (~) VideoAffineTransformationMeta
    type AttrGetType VideoAffineTransformationMetaMetaFieldInfo = Gst.Meta.Meta
    type AttrLabel VideoAffineTransformationMetaMetaFieldInfo = "meta"
    type AttrOrigin VideoAffineTransformationMetaMetaFieldInfo = VideoAffineTransformationMeta
    attrGet _ = getVideoAffineTransformationMetaMeta
    attrSet _ = undefined
    attrConstruct = undefined
    attrClear _ = undefined

videoAffineTransformationMeta_meta :: AttrLabelProxy "meta"
videoAffineTransformationMeta_meta = AttrLabelProxy

#endif


-- XXX Skipped attribute for "VideoAffineTransformationMeta:matrix" :: Not implemented: "Don't know how to unpack C array of type TCArray False 16 (-1) (TBasicType TFloat)"

#if ENABLE_OVERLOADING
instance O.HasAttributeList VideoAffineTransformationMeta
type instance O.AttributeList VideoAffineTransformationMeta = VideoAffineTransformationMetaAttributeList
type VideoAffineTransformationMetaAttributeList = ('[ '("meta", VideoAffineTransformationMetaMetaFieldInfo)] :: [(Symbol, *)])
#endif

-- method VideoAffineTransformationMeta::apply_matrix
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "meta", argType = TInterface (Name {namespace = "GstVideo", name = "VideoAffineTransformationMeta"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstVideoAffineTransformationMeta", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "matrix", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a 4x4 transformation matrix to be applied", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_affine_transformation_meta_apply_matrix" gst_video_affine_transformation_meta_apply_matrix ::
    Ptr VideoAffineTransformationMeta ->    -- meta : TInterface (Name {namespace = "GstVideo", name = "VideoAffineTransformationMeta"})
    CFloat ->                               -- matrix : TBasicType TFloat
    IO ()

{- |
Apply a transformation using the given 4x4 transformation matrix.
Performs the multiplication, meta->matrix X matrix.

/Since: 1.8/
-}
videoAffineTransformationMetaApplyMatrix ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoAffineTransformationMeta
    {- ^ /@meta@/: a 'GI.GstVideo.Structs.VideoAffineTransformationMeta.VideoAffineTransformationMeta' -}
    -> Float
    {- ^ /@matrix@/: a 4x4 transformation matrix to be applied -}
    -> m ()
videoAffineTransformationMetaApplyMatrix meta matrix = liftIO $ do
    meta' <- unsafeManagedPtrGetPtr meta
    let matrix' = realToFrac matrix
    gst_video_affine_transformation_meta_apply_matrix meta' matrix'
    touchManagedPtr meta
    return ()

#if ENABLE_OVERLOADING
data VideoAffineTransformationMetaApplyMatrixMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m) => O.MethodInfo VideoAffineTransformationMetaApplyMatrixMethodInfo VideoAffineTransformationMeta signature where
    overloadedMethod _ = videoAffineTransformationMetaApplyMatrix

#endif

-- method VideoAffineTransformationMeta::get_info
-- method type : MemberFunction
-- Args : []
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "Gst", name = "MetaInfo"}))
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_affine_transformation_meta_get_info" gst_video_affine_transformation_meta_get_info ::
    IO (Ptr Gst.MetaInfo.MetaInfo)

{- |
/No description available in the introspection data./
-}
videoAffineTransformationMetaGetInfo ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Gst.MetaInfo.MetaInfo
videoAffineTransformationMetaGetInfo  = liftIO $ do
    result <- gst_video_affine_transformation_meta_get_info
    checkUnexpectedReturnNULL "videoAffineTransformationMetaGetInfo" result
    result' <- (newPtr Gst.MetaInfo.MetaInfo) result
    return result'

#if ENABLE_OVERLOADING
#endif

#if ENABLE_OVERLOADING
type family ResolveVideoAffineTransformationMetaMethod (t :: Symbol) (o :: *) :: * where
    ResolveVideoAffineTransformationMetaMethod "applyMatrix" o = VideoAffineTransformationMetaApplyMatrixMethodInfo
    ResolveVideoAffineTransformationMetaMethod l o = O.MethodResolutionFailed l o

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