{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.GstVideo.Structs.VideoChromaResample
    ( 

-- * Exported types
    VideoChromaResample(..)                 ,
    noVideoChromaResample                   ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveVideoChromaResampleMethod        ,
#endif


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    VideoChromaResampleFreeMethodInfo       ,
#endif
    videoChromaResampleFree                 ,


-- ** getInfo #method:getInfo#

#if defined(ENABLE_OVERLOADING)
    VideoChromaResampleGetInfoMethodInfo    ,
#endif
    videoChromaResampleGetInfo              ,




    ) 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


-- | Memory-managed wrapper type.
newtype VideoChromaResample = VideoChromaResample (ManagedPtr VideoChromaResample)
    deriving (VideoChromaResample -> VideoChromaResample -> Bool
(VideoChromaResample -> VideoChromaResample -> Bool)
-> (VideoChromaResample -> VideoChromaResample -> Bool)
-> Eq VideoChromaResample
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VideoChromaResample -> VideoChromaResample -> Bool
$c/= :: VideoChromaResample -> VideoChromaResample -> Bool
== :: VideoChromaResample -> VideoChromaResample -> Bool
$c== :: VideoChromaResample -> VideoChromaResample -> Bool
Eq)
-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance WrappedPtr VideoChromaResample where
    wrappedPtrCalloc :: IO (Ptr VideoChromaResample)
wrappedPtrCalloc = Ptr VideoChromaResample -> IO (Ptr VideoChromaResample)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VideoChromaResample
forall a. Ptr a
nullPtr
    wrappedPtrCopy :: VideoChromaResample -> IO VideoChromaResample
wrappedPtrCopy = VideoChromaResample -> IO VideoChromaResample
forall (m :: * -> *) a. Monad m => a -> m a
return
    wrappedPtrFree :: Maybe (GDestroyNotify VideoChromaResample)
wrappedPtrFree = Maybe (GDestroyNotify VideoChromaResample)
forall a. Maybe a
Nothing

-- | A convenience alias for `Nothing` :: `Maybe` `VideoChromaResample`.
noVideoChromaResample :: Maybe VideoChromaResample
noVideoChromaResample :: Maybe VideoChromaResample
noVideoChromaResample = Maybe VideoChromaResample
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList VideoChromaResample
type instance O.AttributeList VideoChromaResample = VideoChromaResampleAttributeList
type VideoChromaResampleAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method VideoChromaResample::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "resample"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoChromaResample" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstVideoChromaResample"
--                 , 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_chroma_resample_free" gst_video_chroma_resample_free :: 
    Ptr VideoChromaResample ->              -- resample : TInterface (Name {namespace = "GstVideo", name = "VideoChromaResample"})
    IO ()

-- | Free /@resample@/
videoChromaResampleFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoChromaResample
    -- ^ /@resample@/: a t'GI.GstVideo.Structs.VideoChromaResample.VideoChromaResample'
    -> m ()
videoChromaResampleFree :: VideoChromaResample -> m ()
videoChromaResampleFree resample :: VideoChromaResample
resample = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr VideoChromaResample
resample' <- VideoChromaResample -> IO (Ptr VideoChromaResample)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VideoChromaResample
resample
    Ptr VideoChromaResample -> IO ()
gst_video_chroma_resample_free Ptr VideoChromaResample
resample'
    VideoChromaResample -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VideoChromaResample
resample
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data VideoChromaResampleFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo VideoChromaResampleFreeMethodInfo VideoChromaResample signature where
    overloadedMethod = videoChromaResampleFree

#endif

-- method VideoChromaResample::get_info
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "resample"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoChromaResample" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstVideoChromaResample"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_lines"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of input lines"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the first line" , 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_chroma_resample_get_info" gst_video_chroma_resample_get_info :: 
    Ptr VideoChromaResample ->              -- resample : TInterface (Name {namespace = "GstVideo", name = "VideoChromaResample"})
    Word32 ->                               -- n_lines : TBasicType TUInt
    Int32 ->                                -- offset : TBasicType TInt
    IO ()

-- | The resampler must be fed /@nLines@/ at a time. The first line should be
-- at /@offset@/.
videoChromaResampleGetInfo ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoChromaResample
    -- ^ /@resample@/: a t'GI.GstVideo.Structs.VideoChromaResample.VideoChromaResample'
    -> Word32
    -- ^ /@nLines@/: the number of input lines
    -> Int32
    -- ^ /@offset@/: the first line
    -> m ()
videoChromaResampleGetInfo :: VideoChromaResample -> Word32 -> Int32 -> m ()
videoChromaResampleGetInfo resample :: VideoChromaResample
resample nLines :: Word32
nLines offset :: Int32
offset = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr VideoChromaResample
resample' <- VideoChromaResample -> IO (Ptr VideoChromaResample)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VideoChromaResample
resample
    Ptr VideoChromaResample -> Word32 -> Int32 -> IO ()
gst_video_chroma_resample_get_info Ptr VideoChromaResample
resample' Word32
nLines Int32
offset
    VideoChromaResample -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VideoChromaResample
resample
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data VideoChromaResampleGetInfoMethodInfo
instance (signature ~ (Word32 -> Int32 -> m ()), MonadIO m) => O.MethodInfo VideoChromaResampleGetInfoMethodInfo VideoChromaResample signature where
    overloadedMethod = videoChromaResampleGetInfo

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveVideoChromaResampleMethod (t :: Symbol) (o :: *) :: * where
    ResolveVideoChromaResampleMethod "free" o = VideoChromaResampleFreeMethodInfo
    ResolveVideoChromaResampleMethod "getInfo" o = VideoChromaResampleGetInfoMethodInfo
    ResolveVideoChromaResampleMethod l o = O.MethodResolutionFailed l o

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

#endif