{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The opaque base class object for all encoding profiles. This contains generic
-- information like name, description, format and preset.

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

module GI.GstPbutils.Objects.EncodingProfile
    ( 

-- * Exported types
    EncodingProfile(..)                     ,
    IsEncodingProfile                       ,
    toEncodingProfile                       ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [copy]("GI.GstPbutils.Objects.EncodingProfile#g:method:copy"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isEnabled]("GI.GstPbutils.Objects.EncodingProfile#g:method:isEnabled"), [isEqual]("GI.GstPbutils.Objects.EncodingProfile#g:method:isEqual"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAllowDynamicOutput]("GI.GstPbutils.Objects.EncodingProfile#g:method:getAllowDynamicOutput"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDescription]("GI.GstPbutils.Objects.EncodingProfile#g:method:getDescription"), [getElementProperties]("GI.GstPbutils.Objects.EncodingProfile#g:method:getElementProperties"), [getFileExtension]("GI.GstPbutils.Objects.EncodingProfile#g:method:getFileExtension"), [getFormat]("GI.GstPbutils.Objects.EncodingProfile#g:method:getFormat"), [getInputCaps]("GI.GstPbutils.Objects.EncodingProfile#g:method:getInputCaps"), [getName]("GI.GstPbutils.Objects.EncodingProfile#g:method:getName"), [getPresence]("GI.GstPbutils.Objects.EncodingProfile#g:method:getPresence"), [getPreset]("GI.GstPbutils.Objects.EncodingProfile#g:method:getPreset"), [getPresetName]("GI.GstPbutils.Objects.EncodingProfile#g:method:getPresetName"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRestriction]("GI.GstPbutils.Objects.EncodingProfile#g:method:getRestriction"), [getSingleSegment]("GI.GstPbutils.Objects.EncodingProfile#g:method:getSingleSegment"), [getTypeNick]("GI.GstPbutils.Objects.EncodingProfile#g:method:getTypeNick").
-- 
-- ==== Setters
-- [setAllowDynamicOutput]("GI.GstPbutils.Objects.EncodingProfile#g:method:setAllowDynamicOutput"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDescription]("GI.GstPbutils.Objects.EncodingProfile#g:method:setDescription"), [setElementProperties]("GI.GstPbutils.Objects.EncodingProfile#g:method:setElementProperties"), [setEnabled]("GI.GstPbutils.Objects.EncodingProfile#g:method:setEnabled"), [setFormat]("GI.GstPbutils.Objects.EncodingProfile#g:method:setFormat"), [setName]("GI.GstPbutils.Objects.EncodingProfile#g:method:setName"), [setPresence]("GI.GstPbutils.Objects.EncodingProfile#g:method:setPresence"), [setPreset]("GI.GstPbutils.Objects.EncodingProfile#g:method:setPreset"), [setPresetName]("GI.GstPbutils.Objects.EncodingProfile#g:method:setPresetName"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setRestriction]("GI.GstPbutils.Objects.EncodingProfile#g:method:setRestriction"), [setSingleSegment]("GI.GstPbutils.Objects.EncodingProfile#g:method:setSingleSegment").

#if defined(ENABLE_OVERLOADING)
    ResolveEncodingProfileMethod            ,
#endif

-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileCopyMethodInfo           ,
#endif
    encodingProfileCopy                     ,


-- ** find #method:find#

    encodingProfileFind                     ,


-- ** fromDiscoverer #method:fromDiscoverer#

    encodingProfileFromDiscoverer           ,


-- ** getAllowDynamicOutput #method:getAllowDynamicOutput#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileGetAllowDynamicOutputMethodInfo,
#endif
    encodingProfileGetAllowDynamicOutput    ,


-- ** getDescription #method:getDescription#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileGetDescriptionMethodInfo ,
#endif
    encodingProfileGetDescription           ,


-- ** getElementProperties #method:getElementProperties#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileGetElementPropertiesMethodInfo,
#endif
    encodingProfileGetElementProperties     ,


-- ** getFileExtension #method:getFileExtension#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileGetFileExtensionMethodInfo,
#endif
    encodingProfileGetFileExtension         ,


-- ** getFormat #method:getFormat#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileGetFormatMethodInfo      ,
#endif
    encodingProfileGetFormat                ,


-- ** getInputCaps #method:getInputCaps#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileGetInputCapsMethodInfo   ,
#endif
    encodingProfileGetInputCaps             ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileGetNameMethodInfo        ,
#endif
    encodingProfileGetName                  ,


-- ** getPresence #method:getPresence#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileGetPresenceMethodInfo    ,
#endif
    encodingProfileGetPresence              ,


-- ** getPreset #method:getPreset#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileGetPresetMethodInfo      ,
#endif
    encodingProfileGetPreset                ,


-- ** getPresetName #method:getPresetName#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileGetPresetNameMethodInfo  ,
#endif
    encodingProfileGetPresetName            ,


-- ** getRestriction #method:getRestriction#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileGetRestrictionMethodInfo ,
#endif
    encodingProfileGetRestriction           ,


-- ** getSingleSegment #method:getSingleSegment#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileGetSingleSegmentMethodInfo,
#endif
    encodingProfileGetSingleSegment         ,


-- ** getTypeNick #method:getTypeNick#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileGetTypeNickMethodInfo    ,
#endif
    encodingProfileGetTypeNick              ,


-- ** isEnabled #method:isEnabled#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileIsEnabledMethodInfo      ,
#endif
    encodingProfileIsEnabled                ,


-- ** isEqual #method:isEqual#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileIsEqualMethodInfo        ,
#endif
    encodingProfileIsEqual                  ,


-- ** setAllowDynamicOutput #method:setAllowDynamicOutput#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileSetAllowDynamicOutputMethodInfo,
#endif
    encodingProfileSetAllowDynamicOutput    ,


-- ** setDescription #method:setDescription#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileSetDescriptionMethodInfo ,
#endif
    encodingProfileSetDescription           ,


-- ** setElementProperties #method:setElementProperties#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileSetElementPropertiesMethodInfo,
#endif
    encodingProfileSetElementProperties     ,


-- ** setEnabled #method:setEnabled#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileSetEnabledMethodInfo     ,
#endif
    encodingProfileSetEnabled               ,


-- ** setFormat #method:setFormat#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileSetFormatMethodInfo      ,
#endif
    encodingProfileSetFormat                ,


-- ** setName #method:setName#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileSetNameMethodInfo        ,
#endif
    encodingProfileSetName                  ,


-- ** setPresence #method:setPresence#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileSetPresenceMethodInfo    ,
#endif
    encodingProfileSetPresence              ,


-- ** setPreset #method:setPreset#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileSetPresetMethodInfo      ,
#endif
    encodingProfileSetPreset                ,


-- ** setPresetName #method:setPresetName#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileSetPresetNameMethodInfo  ,
#endif
    encodingProfileSetPresetName            ,


-- ** setRestriction #method:setRestriction#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileSetRestrictionMethodInfo ,
#endif
    encodingProfileSetRestriction           ,


-- ** setSingleSegment #method:setSingleSegment#

#if defined(ENABLE_OVERLOADING)
    EncodingProfileSetSingleSegmentMethodInfo,
#endif
    encodingProfileSetSingleSegment         ,




 -- * Properties


-- ** elementProperties #attr:elementProperties#
-- | A t'GI.Gst.Structs.Structure.Structure' defining the properties to be set to the element
-- the profile represents.
-- 
-- For example for @av1enc@:
-- 
-- >element-properties,row-mt=true, end-usage=vbr
-- 
-- 
-- /Since: 1.20/

#if defined(ENABLE_OVERLOADING)
    EncodingProfileElementPropertiesPropertyInfo,
#endif
    clearEncodingProfileElementProperties   ,
    constructEncodingProfileElementProperties,
#if defined(ENABLE_OVERLOADING)
    encodingProfileElementProperties        ,
#endif
    getEncodingProfileElementProperties     ,
    setEncodingProfileElementProperties     ,


-- ** restrictionCaps #attr:restrictionCaps#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    EncodingProfileRestrictionCapsPropertyInfo,
#endif
    clearEncodingProfileRestrictionCaps     ,
    constructEncodingProfileRestrictionCaps ,
#if defined(ENABLE_OVERLOADING)
    encodingProfileRestrictionCaps          ,
#endif
    getEncodingProfileRestrictionCaps       ,
    setEncodingProfileRestrictionCaps       ,




    ) 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 GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gst.Structs.Caps as Gst.Caps
import qualified GI.Gst.Structs.Structure as Gst.Structure
import {-# SOURCE #-} qualified GI.GstPbutils.Objects.DiscovererInfo as GstPbutils.DiscovererInfo

-- | Memory-managed wrapper type.
newtype EncodingProfile = EncodingProfile (SP.ManagedPtr EncodingProfile)
    deriving (EncodingProfile -> EncodingProfile -> Bool
(EncodingProfile -> EncodingProfile -> Bool)
-> (EncodingProfile -> EncodingProfile -> Bool)
-> Eq EncodingProfile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EncodingProfile -> EncodingProfile -> Bool
== :: EncodingProfile -> EncodingProfile -> Bool
$c/= :: EncodingProfile -> EncodingProfile -> Bool
/= :: EncodingProfile -> EncodingProfile -> Bool
Eq)

instance SP.ManagedPtrNewtype EncodingProfile where
    toManagedPtr :: EncodingProfile -> ManagedPtr EncodingProfile
toManagedPtr (EncodingProfile ManagedPtr EncodingProfile
p) = ManagedPtr EncodingProfile
p

foreign import ccall "gst_encoding_profile_get_type"
    c_gst_encoding_profile_get_type :: IO B.Types.GType

instance B.Types.TypedObject EncodingProfile where
    glibType :: IO GType
glibType = IO GType
c_gst_encoding_profile_get_type

instance B.Types.GObject EncodingProfile

-- | Type class for types which can be safely cast to `EncodingProfile`, for instance with `toEncodingProfile`.
class (SP.GObject o, O.IsDescendantOf EncodingProfile o) => IsEncodingProfile o
instance (SP.GObject o, O.IsDescendantOf EncodingProfile o) => IsEncodingProfile o

instance O.HasParentTypes EncodingProfile
type instance O.ParentTypes EncodingProfile = '[GObject.Object.Object]

-- | Cast to `EncodingProfile`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toEncodingProfile :: (MIO.MonadIO m, IsEncodingProfile o) => o -> m EncodingProfile
toEncodingProfile :: forall (m :: * -> *) o.
(MonadIO m, IsEncodingProfile o) =>
o -> m EncodingProfile
toEncodingProfile = IO EncodingProfile -> m EncodingProfile
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO EncodingProfile -> m EncodingProfile)
-> (o -> IO EncodingProfile) -> o -> m EncodingProfile
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr EncodingProfile -> EncodingProfile)
-> o -> IO EncodingProfile
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr EncodingProfile -> EncodingProfile
EncodingProfile

-- | Convert 'EncodingProfile' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe EncodingProfile) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gst_encoding_profile_get_type
    gvalueSet_ :: Ptr GValue -> Maybe EncodingProfile -> IO ()
gvalueSet_ Ptr GValue
gv Maybe EncodingProfile
P.Nothing = Ptr GValue -> Ptr EncodingProfile -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr EncodingProfile
forall a. Ptr a
FP.nullPtr :: FP.Ptr EncodingProfile)
    gvalueSet_ Ptr GValue
gv (P.Just EncodingProfile
obj) = EncodingProfile -> (Ptr EncodingProfile -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr EncodingProfile
obj (Ptr GValue -> Ptr EncodingProfile -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe EncodingProfile)
gvalueGet_ Ptr GValue
gv = do
        Ptr EncodingProfile
ptr <- Ptr GValue -> IO (Ptr EncodingProfile)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr EncodingProfile)
        if Ptr EncodingProfile
ptr Ptr EncodingProfile -> Ptr EncodingProfile -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr EncodingProfile
forall a. Ptr a
FP.nullPtr
        then EncodingProfile -> Maybe EncodingProfile
forall a. a -> Maybe a
P.Just (EncodingProfile -> Maybe EncodingProfile)
-> IO EncodingProfile -> IO (Maybe EncodingProfile)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr EncodingProfile -> EncodingProfile)
-> Ptr EncodingProfile -> IO EncodingProfile
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr EncodingProfile -> EncodingProfile
EncodingProfile Ptr EncodingProfile
ptr
        else Maybe EncodingProfile -> IO (Maybe EncodingProfile)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe EncodingProfile
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveEncodingProfileMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveEncodingProfileMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveEncodingProfileMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveEncodingProfileMethod "copy" o = EncodingProfileCopyMethodInfo
    ResolveEncodingProfileMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveEncodingProfileMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveEncodingProfileMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveEncodingProfileMethod "isEnabled" o = EncodingProfileIsEnabledMethodInfo
    ResolveEncodingProfileMethod "isEqual" o = EncodingProfileIsEqualMethodInfo
    ResolveEncodingProfileMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveEncodingProfileMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveEncodingProfileMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveEncodingProfileMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveEncodingProfileMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveEncodingProfileMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveEncodingProfileMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveEncodingProfileMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveEncodingProfileMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveEncodingProfileMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveEncodingProfileMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveEncodingProfileMethod "getAllowDynamicOutput" o = EncodingProfileGetAllowDynamicOutputMethodInfo
    ResolveEncodingProfileMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveEncodingProfileMethod "getDescription" o = EncodingProfileGetDescriptionMethodInfo
    ResolveEncodingProfileMethod "getElementProperties" o = EncodingProfileGetElementPropertiesMethodInfo
    ResolveEncodingProfileMethod "getFileExtension" o = EncodingProfileGetFileExtensionMethodInfo
    ResolveEncodingProfileMethod "getFormat" o = EncodingProfileGetFormatMethodInfo
    ResolveEncodingProfileMethod "getInputCaps" o = EncodingProfileGetInputCapsMethodInfo
    ResolveEncodingProfileMethod "getName" o = EncodingProfileGetNameMethodInfo
    ResolveEncodingProfileMethod "getPresence" o = EncodingProfileGetPresenceMethodInfo
    ResolveEncodingProfileMethod "getPreset" o = EncodingProfileGetPresetMethodInfo
    ResolveEncodingProfileMethod "getPresetName" o = EncodingProfileGetPresetNameMethodInfo
    ResolveEncodingProfileMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveEncodingProfileMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveEncodingProfileMethod "getRestriction" o = EncodingProfileGetRestrictionMethodInfo
    ResolveEncodingProfileMethod "getSingleSegment" o = EncodingProfileGetSingleSegmentMethodInfo
    ResolveEncodingProfileMethod "getTypeNick" o = EncodingProfileGetTypeNickMethodInfo
    ResolveEncodingProfileMethod "setAllowDynamicOutput" o = EncodingProfileSetAllowDynamicOutputMethodInfo
    ResolveEncodingProfileMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveEncodingProfileMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveEncodingProfileMethod "setDescription" o = EncodingProfileSetDescriptionMethodInfo
    ResolveEncodingProfileMethod "setElementProperties" o = EncodingProfileSetElementPropertiesMethodInfo
    ResolveEncodingProfileMethod "setEnabled" o = EncodingProfileSetEnabledMethodInfo
    ResolveEncodingProfileMethod "setFormat" o = EncodingProfileSetFormatMethodInfo
    ResolveEncodingProfileMethod "setName" o = EncodingProfileSetNameMethodInfo
    ResolveEncodingProfileMethod "setPresence" o = EncodingProfileSetPresenceMethodInfo
    ResolveEncodingProfileMethod "setPreset" o = EncodingProfileSetPresetMethodInfo
    ResolveEncodingProfileMethod "setPresetName" o = EncodingProfileSetPresetNameMethodInfo
    ResolveEncodingProfileMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveEncodingProfileMethod "setRestriction" o = EncodingProfileSetRestrictionMethodInfo
    ResolveEncodingProfileMethod "setSingleSegment" o = EncodingProfileSetSingleSegmentMethodInfo
    ResolveEncodingProfileMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveEncodingProfileMethod t EncodingProfile, O.OverloadedMethod info EncodingProfile p) => OL.IsLabel t (EncodingProfile -> 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 ~ ResolveEncodingProfileMethod t EncodingProfile, O.OverloadedMethod info EncodingProfile p, R.HasField t EncodingProfile p) => R.HasField t EncodingProfile p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveEncodingProfileMethod t EncodingProfile, O.OverloadedMethodInfo info EncodingProfile) => OL.IsLabel t (O.MethodProxy info EncodingProfile) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "element-properties"
   -- Type: TInterface (Name {namespace = "Gst", name = "Structure"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@element-properties@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' encodingProfile #elementProperties
-- @
getEncodingProfileElementProperties :: (MonadIO m, IsEncodingProfile o) => o -> m (Maybe Gst.Structure.Structure)
getEncodingProfileElementProperties :: forall (m :: * -> *) o.
(MonadIO m, IsEncodingProfile o) =>
o -> m (Maybe Structure)
getEncodingProfileElementProperties o
obj = IO (Maybe Structure) -> m (Maybe Structure)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Structure) -> m (Maybe Structure))
-> IO (Maybe Structure) -> m (Maybe Structure)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr Structure -> Structure)
-> IO (Maybe Structure)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"element-properties" ManagedPtr Structure -> Structure
Gst.Structure.Structure

-- | Set the value of the “@element-properties@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' encodingProfile [ #elementProperties 'Data.GI.Base.Attributes.:=' value ]
-- @
setEncodingProfileElementProperties :: (MonadIO m, IsEncodingProfile o) => o -> Gst.Structure.Structure -> m ()
setEncodingProfileElementProperties :: forall (m :: * -> *) o.
(MonadIO m, IsEncodingProfile o) =>
o -> Structure -> m ()
setEncodingProfileElementProperties o
obj Structure
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Structure -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"element-properties" (Structure -> Maybe Structure
forall a. a -> Maybe a
Just Structure
val)

-- | Construct a `GValueConstruct` with valid value for the “@element-properties@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEncodingProfileElementProperties :: (IsEncodingProfile o, MIO.MonadIO m) => Gst.Structure.Structure -> m (GValueConstruct o)
constructEncodingProfileElementProperties :: forall o (m :: * -> *).
(IsEncodingProfile o, MonadIO m) =>
Structure -> m (GValueConstruct o)
constructEncodingProfileElementProperties Structure
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Structure -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"element-properties" (Structure -> Maybe Structure
forall a. a -> Maybe a
P.Just Structure
val)

-- | Set the value of the “@element-properties@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #elementProperties
-- @
clearEncodingProfileElementProperties :: (MonadIO m, IsEncodingProfile o) => o -> m ()
clearEncodingProfileElementProperties :: forall (m :: * -> *) o.
(MonadIO m, IsEncodingProfile o) =>
o -> m ()
clearEncodingProfileElementProperties o
obj = 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
$ o -> String -> Maybe Structure -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"element-properties" (Maybe Structure
forall a. Maybe a
Nothing :: Maybe Gst.Structure.Structure)

#if defined(ENABLE_OVERLOADING)
data EncodingProfileElementPropertiesPropertyInfo
instance AttrInfo EncodingProfileElementPropertiesPropertyInfo where
    type AttrAllowedOps EncodingProfileElementPropertiesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EncodingProfileElementPropertiesPropertyInfo = IsEncodingProfile
    type AttrSetTypeConstraint EncodingProfileElementPropertiesPropertyInfo = (~) Gst.Structure.Structure
    type AttrTransferTypeConstraint EncodingProfileElementPropertiesPropertyInfo = (~) Gst.Structure.Structure
    type AttrTransferType EncodingProfileElementPropertiesPropertyInfo = Gst.Structure.Structure
    type AttrGetType EncodingProfileElementPropertiesPropertyInfo = (Maybe Gst.Structure.Structure)
    type AttrLabel EncodingProfileElementPropertiesPropertyInfo = "element-properties"
    type AttrOrigin EncodingProfileElementPropertiesPropertyInfo = EncodingProfile
    attrGet = getEncodingProfileElementProperties
    attrSet = setEncodingProfileElementProperties
    attrTransfer _ v = do
        return v
    attrConstruct = constructEncodingProfileElementProperties
    attrClear = clearEncodingProfileElementProperties
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.elementProperties"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#g:attr:elementProperties"
        })
#endif

-- VVV Prop "restriction-caps"
   -- Type: TInterface (Name {namespace = "Gst", name = "Caps"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@restriction-caps@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' encodingProfile #restrictionCaps
-- @
getEncodingProfileRestrictionCaps :: (MonadIO m, IsEncodingProfile o) => o -> m (Maybe Gst.Caps.Caps)
getEncodingProfileRestrictionCaps :: forall (m :: * -> *) o.
(MonadIO m, IsEncodingProfile o) =>
o -> m (Maybe Caps)
getEncodingProfileRestrictionCaps o
obj = IO (Maybe Caps) -> m (Maybe Caps)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Caps) -> m (Maybe Caps))
-> IO (Maybe Caps) -> m (Maybe Caps)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Caps -> Caps) -> IO (Maybe Caps)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"restriction-caps" ManagedPtr Caps -> Caps
Gst.Caps.Caps

-- | Set the value of the “@restriction-caps@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' encodingProfile [ #restrictionCaps 'Data.GI.Base.Attributes.:=' value ]
-- @
setEncodingProfileRestrictionCaps :: (MonadIO m, IsEncodingProfile o) => o -> Gst.Caps.Caps -> m ()
setEncodingProfileRestrictionCaps :: forall (m :: * -> *) o.
(MonadIO m, IsEncodingProfile o) =>
o -> Caps -> m ()
setEncodingProfileRestrictionCaps o
obj Caps
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Caps -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"restriction-caps" (Caps -> Maybe Caps
forall a. a -> Maybe a
Just Caps
val)

-- | Construct a `GValueConstruct` with valid value for the “@restriction-caps@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEncodingProfileRestrictionCaps :: (IsEncodingProfile o, MIO.MonadIO m) => Gst.Caps.Caps -> m (GValueConstruct o)
constructEncodingProfileRestrictionCaps :: forall o (m :: * -> *).
(IsEncodingProfile o, MonadIO m) =>
Caps -> m (GValueConstruct o)
constructEncodingProfileRestrictionCaps Caps
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Caps -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"restriction-caps" (Caps -> Maybe Caps
forall a. a -> Maybe a
P.Just Caps
val)

-- | Set the value of the “@restriction-caps@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #restrictionCaps
-- @
clearEncodingProfileRestrictionCaps :: (MonadIO m, IsEncodingProfile o) => o -> m ()
clearEncodingProfileRestrictionCaps :: forall (m :: * -> *) o.
(MonadIO m, IsEncodingProfile o) =>
o -> m ()
clearEncodingProfileRestrictionCaps o
obj = 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
$ o -> String -> Maybe Caps -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"restriction-caps" (Maybe Caps
forall a. Maybe a
Nothing :: Maybe Gst.Caps.Caps)

#if defined(ENABLE_OVERLOADING)
data EncodingProfileRestrictionCapsPropertyInfo
instance AttrInfo EncodingProfileRestrictionCapsPropertyInfo where
    type AttrAllowedOps EncodingProfileRestrictionCapsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EncodingProfileRestrictionCapsPropertyInfo = IsEncodingProfile
    type AttrSetTypeConstraint EncodingProfileRestrictionCapsPropertyInfo = (~) Gst.Caps.Caps
    type AttrTransferTypeConstraint EncodingProfileRestrictionCapsPropertyInfo = (~) Gst.Caps.Caps
    type AttrTransferType EncodingProfileRestrictionCapsPropertyInfo = Gst.Caps.Caps
    type AttrGetType EncodingProfileRestrictionCapsPropertyInfo = (Maybe Gst.Caps.Caps)
    type AttrLabel EncodingProfileRestrictionCapsPropertyInfo = "restriction-caps"
    type AttrOrigin EncodingProfileRestrictionCapsPropertyInfo = EncodingProfile
    attrGet = getEncodingProfileRestrictionCaps
    attrSet = setEncodingProfileRestrictionCaps
    attrTransfer _ v = do
        return v
    attrConstruct = constructEncodingProfileRestrictionCaps
    attrClear = clearEncodingProfileRestrictionCaps
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.restrictionCaps"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#g:attr:restrictionCaps"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EncodingProfile
type instance O.AttributeList EncodingProfile = EncodingProfileAttributeList
type EncodingProfileAttributeList = ('[ '("elementProperties", EncodingProfileElementPropertiesPropertyInfo), '("restrictionCaps", EncodingProfileRestrictionCapsPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
encodingProfileElementProperties :: AttrLabelProxy "elementProperties"
encodingProfileElementProperties = AttrLabelProxy

encodingProfileRestrictionCaps :: AttrLabelProxy "restrictionCaps"
encodingProfileRestrictionCaps = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList EncodingProfile = EncodingProfileSignalList
type EncodingProfileSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method EncodingProfile::copy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GstEncodingProfile to copy"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "GstPbutils" , name = "EncodingProfile" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_copy" gst_encoding_profile_copy :: 
    Ptr EncodingProfile ->                  -- self : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    IO (Ptr EncodingProfile)

-- | Makes a deep copy of /@self@/
-- 
-- /Since: 1.12/
encodingProfileCopy ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@self@/: The t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile' to copy
    -> m EncodingProfile
    -- ^ __Returns:__ The copy of /@self@/
encodingProfileCopy :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> m EncodingProfile
encodingProfileCopy a
self = IO EncodingProfile -> m EncodingProfile
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EncodingProfile -> m EncodingProfile)
-> IO EncodingProfile -> m EncodingProfile
forall a b. (a -> b) -> a -> b
$ do
    Ptr EncodingProfile
self' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr EncodingProfile
result <- Ptr EncodingProfile -> IO (Ptr EncodingProfile)
gst_encoding_profile_copy Ptr EncodingProfile
self'
    Text -> Ptr EncodingProfile -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"encodingProfileCopy" Ptr EncodingProfile
result
    EncodingProfile
result' <- ((ManagedPtr EncodingProfile -> EncodingProfile)
-> Ptr EncodingProfile -> IO EncodingProfile
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr EncodingProfile -> EncodingProfile
EncodingProfile) Ptr EncodingProfile
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    EncodingProfile -> IO EncodingProfile
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return EncodingProfile
result'

#if defined(ENABLE_OVERLOADING)
data EncodingProfileCopyMethodInfo
instance (signature ~ (m EncodingProfile), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileCopyMethodInfo a signature where
    overloadedMethod = encodingProfileCopy

instance O.OverloadedMethodInfo EncodingProfileCopyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileCopy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileCopy"
        })


#endif

-- method EncodingProfile::get_allow_dynamic_output
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , 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_encoding_profile_get_allow_dynamic_output" gst_encoding_profile_get_allow_dynamic_output :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    IO CInt

-- | Get whether the format that has been negotiated in at some point can be renegotiated
-- later during the encoding.
encodingProfileGetAllowDynamicOutput ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> m Bool
encodingProfileGetAllowDynamicOutput :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> m Bool
encodingProfileGetAllowDynamicOutput a
profile = 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
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    CInt
result <- Ptr EncodingProfile -> IO CInt
gst_encoding_profile_get_allow_dynamic_output Ptr EncodingProfile
profile'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data EncodingProfileGetAllowDynamicOutputMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileGetAllowDynamicOutputMethodInfo a signature where
    overloadedMethod = encodingProfileGetAllowDynamicOutput

instance O.OverloadedMethodInfo EncodingProfileGetAllowDynamicOutputMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileGetAllowDynamicOutput",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileGetAllowDynamicOutput"
        })


#endif

-- method EncodingProfile::get_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , 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_encoding_profile_get_description" gst_encoding_profile_get_description :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    IO CString

-- | /No description available in the introspection data./
encodingProfileGetDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the description of the profile, can be 'P.Nothing'.
encodingProfileGetDescription :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> m (Maybe Text)
encodingProfileGetDescription a
profile = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    CString
result <- Ptr EncodingProfile -> IO CString
gst_encoding_profile_get_description Ptr EncodingProfile
profile'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data EncodingProfileGetDescriptionMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileGetDescriptionMethodInfo a signature where
    overloadedMethod = encodingProfileGetDescription

instance O.OverloadedMethodInfo EncodingProfileGetDescriptionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileGetDescription",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileGetDescription"
        })


#endif

-- method EncodingProfile::get_element_properties
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Structure" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_get_element_properties" gst_encoding_profile_get_element_properties :: 
    Ptr EncodingProfile ->                  -- self : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    IO (Ptr Gst.Structure.Structure)

-- | /No description available in the introspection data./
-- 
-- /Since: 1.20/
encodingProfileGetElementProperties ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@self@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> m (Maybe Gst.Structure.Structure)
    -- ^ __Returns:__ The properties that are going to be set on the underlying element
encodingProfileGetElementProperties :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> m (Maybe Structure)
encodingProfileGetElementProperties a
self = IO (Maybe Structure) -> m (Maybe Structure)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Structure) -> m (Maybe Structure))
-> IO (Maybe Structure) -> m (Maybe Structure)
forall a b. (a -> b) -> a -> b
$ do
    Ptr EncodingProfile
self' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Structure
result <- Ptr EncodingProfile -> IO (Ptr Structure)
gst_encoding_profile_get_element_properties Ptr EncodingProfile
self'
    Maybe Structure
maybeResult <- Ptr Structure
-> (Ptr Structure -> IO Structure) -> IO (Maybe Structure)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Structure
result ((Ptr Structure -> IO Structure) -> IO (Maybe Structure))
-> (Ptr Structure -> IO Structure) -> IO (Maybe Structure)
forall a b. (a -> b) -> a -> b
$ \Ptr Structure
result' -> do
        Structure
result'' <- ((ManagedPtr Structure -> Structure)
-> Ptr Structure -> IO Structure
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Structure -> Structure
Gst.Structure.Structure) Ptr Structure
result'
        Structure -> IO Structure
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Structure
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Structure -> IO (Maybe Structure)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Structure
maybeResult

#if defined(ENABLE_OVERLOADING)
data EncodingProfileGetElementPropertiesMethodInfo
instance (signature ~ (m (Maybe Gst.Structure.Structure)), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileGetElementPropertiesMethodInfo a signature where
    overloadedMethod = encodingProfileGetElementProperties

instance O.OverloadedMethodInfo EncodingProfileGetElementPropertiesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileGetElementProperties",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileGetElementProperties"
        })


#endif

-- method EncodingProfile::get_file_extension
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , 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_encoding_profile_get_file_extension" gst_encoding_profile_get_file_extension :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    IO CString

-- | /No description available in the introspection data./
encodingProfileGetFileExtension ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ a suitable file extension for /@profile@/, or NULL.
encodingProfileGetFileExtension :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> m (Maybe Text)
encodingProfileGetFileExtension a
profile = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    CString
result <- Ptr EncodingProfile -> IO CString
gst_encoding_profile_get_file_extension Ptr EncodingProfile
profile'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data EncodingProfileGetFileExtensionMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileGetFileExtensionMethodInfo a signature where
    overloadedMethod = encodingProfileGetFileExtension

instance O.OverloadedMethodInfo EncodingProfileGetFileExtensionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileGetFileExtension",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileGetFileExtension"
        })


#endif

-- method EncodingProfile::get_format
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Caps" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_get_format" gst_encoding_profile_get_format :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    IO (Ptr Gst.Caps.Caps)

-- | /No description available in the introspection data./
encodingProfileGetFormat ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> m Gst.Caps.Caps
    -- ^ __Returns:__ (nullable): the t'GI.Gst.Structs.Caps.Caps' corresponding to the media format used
    -- in the profile. Unref after usage.
encodingProfileGetFormat :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> m Caps
encodingProfileGetFormat a
profile = IO Caps -> m Caps
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Caps -> m Caps) -> IO Caps -> m Caps
forall a b. (a -> b) -> a -> b
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    Ptr Caps
result <- Ptr EncodingProfile -> IO (Ptr Caps)
gst_encoding_profile_get_format Ptr EncodingProfile
profile'
    Text -> Ptr Caps -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"encodingProfileGetFormat" Ptr Caps
result
    Caps
result' <- ((ManagedPtr Caps -> Caps) -> Ptr Caps -> IO Caps
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Caps -> Caps
Gst.Caps.Caps) Ptr Caps
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    Caps -> IO Caps
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Caps
result'

#if defined(ENABLE_OVERLOADING)
data EncodingProfileGetFormatMethodInfo
instance (signature ~ (m Gst.Caps.Caps), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileGetFormatMethodInfo a signature where
    overloadedMethod = encodingProfileGetFormat

instance O.OverloadedMethodInfo EncodingProfileGetFormatMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileGetFormat",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileGetFormat"
        })


#endif

-- method EncodingProfile::get_input_caps
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Caps" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_get_input_caps" gst_encoding_profile_get_input_caps :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    IO (Ptr Gst.Caps.Caps)

-- | Computes the full output caps that this /@profile@/ will be able to consume.
encodingProfileGetInputCaps ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> m Gst.Caps.Caps
    -- ^ __Returns:__ The full caps the given /@profile@/ can consume. Call
    -- @/gst_caps_unref()/@ when you are done with the caps.
encodingProfileGetInputCaps :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> m Caps
encodingProfileGetInputCaps a
profile = IO Caps -> m Caps
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Caps -> m Caps) -> IO Caps -> m Caps
forall a b. (a -> b) -> a -> b
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    Ptr Caps
result <- Ptr EncodingProfile -> IO (Ptr Caps)
gst_encoding_profile_get_input_caps Ptr EncodingProfile
profile'
    Text -> Ptr Caps -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"encodingProfileGetInputCaps" Ptr Caps
result
    Caps
result' <- ((ManagedPtr Caps -> Caps) -> Ptr Caps -> IO Caps
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Caps -> Caps
Gst.Caps.Caps) Ptr Caps
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    Caps -> IO Caps
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Caps
result'

#if defined(ENABLE_OVERLOADING)
data EncodingProfileGetInputCapsMethodInfo
instance (signature ~ (m Gst.Caps.Caps), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileGetInputCapsMethodInfo a signature where
    overloadedMethod = encodingProfileGetInputCaps

instance O.OverloadedMethodInfo EncodingProfileGetInputCapsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileGetInputCaps",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileGetInputCaps"
        })


#endif

-- method EncodingProfile::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , 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_encoding_profile_get_name" gst_encoding_profile_get_name :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    IO CString

-- | /No description available in the introspection data./
encodingProfileGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the name of the profile, can be 'P.Nothing'.
encodingProfileGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> m (Maybe Text)
encodingProfileGetName a
profile = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    CString
result <- Ptr EncodingProfile -> IO CString
gst_encoding_profile_get_name Ptr EncodingProfile
profile'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data EncodingProfileGetNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileGetNameMethodInfo a signature where
    overloadedMethod = encodingProfileGetName

instance O.OverloadedMethodInfo EncodingProfileGetNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileGetName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileGetName"
        })


#endif

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

foreign import ccall "gst_encoding_profile_get_presence" gst_encoding_profile_get_presence :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    IO Word32

-- | /No description available in the introspection data./
encodingProfileGetPresence ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> m Word32
    -- ^ __Returns:__ The number of times the profile is used in its parent
    -- container profile. If 0, it is not a mandatory stream.
encodingProfileGetPresence :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> m Word32
encodingProfileGetPresence a
profile = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    Word32
result <- Ptr EncodingProfile -> IO Word32
gst_encoding_profile_get_presence Ptr EncodingProfile
profile'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data EncodingProfileGetPresenceMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileGetPresenceMethodInfo a signature where
    overloadedMethod = encodingProfileGetPresence

instance O.OverloadedMethodInfo EncodingProfileGetPresenceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileGetPresence",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileGetPresence"
        })


#endif

-- method EncodingProfile::get_preset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , 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_encoding_profile_get_preset" gst_encoding_profile_get_preset :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    IO CString

-- | /No description available in the introspection data./
encodingProfileGetPreset ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the name of the t'GI.Gst.Interfaces.Preset.Preset' to be used in the profile.
    -- This is the name that has been set when saving the preset.
encodingProfileGetPreset :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> m (Maybe Text)
encodingProfileGetPreset a
profile = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    CString
result <- Ptr EncodingProfile -> IO CString
gst_encoding_profile_get_preset Ptr EncodingProfile
profile'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data EncodingProfileGetPresetMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileGetPresetMethodInfo a signature where
    overloadedMethod = encodingProfileGetPreset

instance O.OverloadedMethodInfo EncodingProfileGetPresetMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileGetPreset",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileGetPreset"
        })


#endif

-- method EncodingProfile::get_preset_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , 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_encoding_profile_get_preset_name" gst_encoding_profile_get_preset_name :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    IO CString

-- | /No description available in the introspection data./
encodingProfileGetPresetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the name of the t'GI.Gst.Interfaces.Preset.Preset' factory to be used in the profile.
encodingProfileGetPresetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> m (Maybe Text)
encodingProfileGetPresetName a
profile = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    CString
result <- Ptr EncodingProfile -> IO CString
gst_encoding_profile_get_preset_name Ptr EncodingProfile
profile'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data EncodingProfileGetPresetNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileGetPresetNameMethodInfo a signature where
    overloadedMethod = encodingProfileGetPresetName

instance O.OverloadedMethodInfo EncodingProfileGetPresetNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileGetPresetName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileGetPresetName"
        })


#endif

-- method EncodingProfile::get_restriction
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Caps" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_get_restriction" gst_encoding_profile_get_restriction :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    IO (Ptr Gst.Caps.Caps)

-- | /No description available in the introspection data./
encodingProfileGetRestriction ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> m (Maybe Gst.Caps.Caps)
    -- ^ __Returns:__ The restriction t'GI.Gst.Structs.Caps.Caps' to apply before the encoder
    -- that will be used in the profile. The fields present in restriction caps are
    -- properties of the raw stream (that is before encoding), such as height and
    -- width for video and depth and sampling rate for audio. Does not apply to
    -- t'GI.GstPbutils.Objects.EncodingContainerProfile.EncodingContainerProfile' (since there is no corresponding raw stream).
    -- Can be 'P.Nothing'. Unref after usage.
encodingProfileGetRestriction :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> m (Maybe Caps)
encodingProfileGetRestriction a
profile = IO (Maybe Caps) -> m (Maybe Caps)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Caps) -> m (Maybe Caps))
-> IO (Maybe Caps) -> m (Maybe Caps)
forall a b. (a -> b) -> a -> b
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    Ptr Caps
result <- Ptr EncodingProfile -> IO (Ptr Caps)
gst_encoding_profile_get_restriction Ptr EncodingProfile
profile'
    Maybe Caps
maybeResult <- Ptr Caps -> (Ptr Caps -> IO Caps) -> IO (Maybe Caps)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Caps
result ((Ptr Caps -> IO Caps) -> IO (Maybe Caps))
-> (Ptr Caps -> IO Caps) -> IO (Maybe Caps)
forall a b. (a -> b) -> a -> b
$ \Ptr Caps
result' -> do
        Caps
result'' <- ((ManagedPtr Caps -> Caps) -> Ptr Caps -> IO Caps
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Caps -> Caps
Gst.Caps.Caps) Ptr Caps
result'
        Caps -> IO Caps
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Caps
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    Maybe Caps -> IO (Maybe Caps)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Caps
maybeResult

#if defined(ENABLE_OVERLOADING)
data EncodingProfileGetRestrictionMethodInfo
instance (signature ~ (m (Maybe Gst.Caps.Caps)), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileGetRestrictionMethodInfo a signature where
    overloadedMethod = encodingProfileGetRestriction

instance O.OverloadedMethodInfo EncodingProfileGetRestrictionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileGetRestriction",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileGetRestriction"
        })


#endif

-- method EncodingProfile::get_single_segment
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , 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_encoding_profile_get_single_segment" gst_encoding_profile_get_single_segment :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    IO CInt

-- | /No description available in the introspection data./
-- 
-- /Since: 1.18/
encodingProfileGetSingleSegment ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> m Bool
    -- ^ __Returns:__ @/TRUE/@ if the stream represented by /@profile@/ should use a single
    -- segment before the encoder, @/FALSE/@ otherwise. This means that buffers will be retimestamped
    -- and segments will be eat so as to appear as one segment.
encodingProfileGetSingleSegment :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> m Bool
encodingProfileGetSingleSegment a
profile = 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
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    CInt
result <- Ptr EncodingProfile -> IO CInt
gst_encoding_profile_get_single_segment Ptr EncodingProfile
profile'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data EncodingProfileGetSingleSegmentMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileGetSingleSegmentMethodInfo a signature where
    overloadedMethod = encodingProfileGetSingleSegment

instance O.OverloadedMethodInfo EncodingProfileGetSingleSegmentMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileGetSingleSegment",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileGetSingleSegment"
        })


#endif

-- method EncodingProfile::get_type_nick
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , 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_encoding_profile_get_type_nick" gst_encoding_profile_get_type_nick :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    IO CString

-- | /No description available in the introspection data./
encodingProfileGetTypeNick ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> m T.Text
    -- ^ __Returns:__ the human-readable name of the type of /@profile@/.
encodingProfileGetTypeNick :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> m Text
encodingProfileGetTypeNick a
profile = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    CString
result <- Ptr EncodingProfile -> IO CString
gst_encoding_profile_get_type_nick Ptr EncodingProfile
profile'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"encodingProfileGetTypeNick" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EncodingProfileGetTypeNickMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileGetTypeNickMethodInfo a signature where
    overloadedMethod = encodingProfileGetTypeNick

instance O.OverloadedMethodInfo EncodingProfileGetTypeNickMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileGetTypeNick",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileGetTypeNick"
        })


#endif

-- method EncodingProfile::is_enabled
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , 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_encoding_profile_is_enabled" gst_encoding_profile_is_enabled :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    IO CInt

-- | /No description available in the introspection data./
encodingProfileIsEnabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -> m Bool
encodingProfileIsEnabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> m Bool
encodingProfileIsEnabled a
profile = 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
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    CInt
result <- Ptr EncodingProfile -> IO CInt
gst_encoding_profile_is_enabled Ptr EncodingProfile
profile'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data EncodingProfileIsEnabledMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileIsEnabledMethodInfo a signature where
    overloadedMethod = encodingProfileIsEnabled

instance O.OverloadedMethodInfo EncodingProfileIsEnabledMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileIsEnabled",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileIsEnabled"
        })


#endif

-- method EncodingProfile::is_equal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , 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_encoding_profile_is_equal" gst_encoding_profile_is_equal :: 
    Ptr EncodingProfile ->                  -- a : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    Ptr EncodingProfile ->                  -- b : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    IO CInt

-- | Checks whether the two t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile' are equal
encodingProfileIsEqual ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a, IsEncodingProfile b) =>
    a
    -- ^ /@a@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> b
    -- ^ /@b@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@a@/ and /@b@/ are equal, else 'P.False'.
encodingProfileIsEqual :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsEncodingProfile a,
 IsEncodingProfile b) =>
a -> b -> m Bool
encodingProfileIsEqual a
a b
b = 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
$ do
    Ptr EncodingProfile
a' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
a
    Ptr EncodingProfile
b' <- b -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
b
    CInt
result <- Ptr EncodingProfile -> Ptr EncodingProfile -> IO CInt
gst_encoding_profile_is_equal Ptr EncodingProfile
a' Ptr EncodingProfile
b'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
a
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
b
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data EncodingProfileIsEqualMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsEncodingProfile a, IsEncodingProfile b) => O.OverloadedMethod EncodingProfileIsEqualMethodInfo a signature where
    overloadedMethod = encodingProfileIsEqual

instance O.OverloadedMethodInfo EncodingProfileIsEqualMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileIsEqual",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileIsEqual"
        })


#endif

-- method EncodingProfile::set_allow_dynamic_output
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "allow_dynamic_output"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Whether the format that has been negotiated first can be renegotiated\nduring the encoding"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_set_allow_dynamic_output" gst_encoding_profile_set_allow_dynamic_output :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    CInt ->                                 -- allow_dynamic_output : TBasicType TBoolean
    IO ()

-- | Sets whether the format that has been negotiated in at some point can be renegotiated
-- later during the encoding.
encodingProfileSetAllowDynamicOutput ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> Bool
    -- ^ /@allowDynamicOutput@/: Whether the format that has been negotiated first can be renegotiated
    -- during the encoding
    -> m ()
encodingProfileSetAllowDynamicOutput :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> Bool -> m ()
encodingProfileSetAllowDynamicOutput a
profile Bool
allowDynamicOutput = 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
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    let allowDynamicOutput' :: CInt
allowDynamicOutput' = (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
allowDynamicOutput
    Ptr EncodingProfile -> CInt -> IO ()
gst_encoding_profile_set_allow_dynamic_output Ptr EncodingProfile
profile' CInt
allowDynamicOutput'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EncodingProfileSetAllowDynamicOutputMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileSetAllowDynamicOutputMethodInfo a signature where
    overloadedMethod = encodingProfileSetAllowDynamicOutput

instance O.OverloadedMethodInfo EncodingProfileSetAllowDynamicOutputMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileSetAllowDynamicOutput",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileSetAllowDynamicOutput"
        })


#endif

-- method EncodingProfile::set_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "description"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the description to set on the profile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_set_description" gst_encoding_profile_set_description :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    CString ->                              -- description : TBasicType TUTF8
    IO ()

-- | Set /@description@/ as the given description for the /@profile@/. A copy of
-- /@description@/ will be made internally.
encodingProfileSetDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> Maybe (T.Text)
    -- ^ /@description@/: the description to set on the profile
    -> m ()
encodingProfileSetDescription :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> Maybe Text -> m ()
encodingProfileSetDescription a
profile Maybe Text
description = 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
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    CString
maybeDescription <- case Maybe Text
description of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jDescription -> do
            CString
jDescription' <- Text -> IO CString
textToCString Text
jDescription
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jDescription'
    Ptr EncodingProfile -> CString -> IO ()
gst_encoding_profile_set_description Ptr EncodingProfile
profile' CString
maybeDescription
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeDescription
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EncodingProfileSetDescriptionMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileSetDescriptionMethodInfo a signature where
    overloadedMethod = encodingProfileSetDescription

instance O.OverloadedMethodInfo EncodingProfileSetDescriptionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileSetDescription",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileSetDescription"
        })


#endif

-- method EncodingProfile::set_element_properties
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "element_properties"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "Structure" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GstStructure defining the properties\nto be set to the element the profile represents."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_set_element_properties" gst_encoding_profile_set_element_properties :: 
    Ptr EncodingProfile ->                  -- self : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    Ptr Gst.Structure.Structure ->          -- element_properties : TInterface (Name {namespace = "Gst", name = "Structure"})
    IO ()

-- | This allows setting the muxing\/encoding element properties.
-- 
-- **Set properties generically**
-- 
-- 
-- === /properties code/
-- > [element-properties, boolean-prop=true, string-prop="hi"]
-- 
-- 
-- **Mapping properties with well known element factories**
-- 
-- 
-- === /properties code/
-- >element-properties-map, map = {
-- >     [openh264enc, gop-size=32, ],
-- >     [x264enc, key-int-max=32, tune=zerolatency],
-- > }
-- 
-- 
-- /Since: 1.20/
encodingProfileSetElementProperties ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@self@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> Gst.Structure.Structure
    -- ^ /@elementProperties@/: A t'GI.Gst.Structs.Structure.Structure' defining the properties
    -- to be set to the element the profile represents.
    -> m ()
encodingProfileSetElementProperties :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> Structure -> m ()
encodingProfileSetElementProperties a
self Structure
elementProperties = 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
$ do
    Ptr EncodingProfile
self' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Structure
elementProperties' <- Structure -> IO (Ptr Structure)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Structure
elementProperties
    Ptr EncodingProfile -> Ptr Structure -> IO ()
gst_encoding_profile_set_element_properties Ptr EncodingProfile
self' Ptr Structure
elementProperties'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Structure -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Structure
elementProperties
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EncodingProfileSetElementPropertiesMethodInfo
instance (signature ~ (Gst.Structure.Structure -> m ()), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileSetElementPropertiesMethodInfo a signature where
    overloadedMethod = encodingProfileSetElementProperties

instance O.OverloadedMethodInfo EncodingProfileSetElementPropertiesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileSetElementProperties",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileSetElementProperties"
        })


#endif

-- method EncodingProfile::set_enabled
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "enabled"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "%FALSE to disable @profile, %TRUE to enable it"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_set_enabled" gst_encoding_profile_set_enabled :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    CInt ->                                 -- enabled : TBasicType TBoolean
    IO ()

-- | Set whether the profile should be used or not.
-- 
-- /Since: 1.6/
encodingProfileSetEnabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> Bool
    -- ^ /@enabled@/: 'P.False' to disable /@profile@/, 'P.True' to enable it
    -> m ()
encodingProfileSetEnabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> Bool -> m ()
encodingProfileSetEnabled a
profile Bool
enabled = 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
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    let enabled' :: CInt
enabled' = (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
enabled
    Ptr EncodingProfile -> CInt -> IO ()
gst_encoding_profile_set_enabled Ptr EncodingProfile
profile' CInt
enabled'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EncodingProfileSetEnabledMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileSetEnabledMethodInfo a signature where
    overloadedMethod = encodingProfileSetEnabled

instance O.OverloadedMethodInfo EncodingProfileSetEnabledMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileSetEnabled",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileSetEnabled"
        })


#endif

-- method EncodingProfile::set_format
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "format"
--           , argType = TInterface Name { namespace = "Gst" , name = "Caps" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the media format to use in the profile."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_set_format" gst_encoding_profile_set_format :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    Ptr Gst.Caps.Caps ->                    -- format : TInterface (Name {namespace = "Gst", name = "Caps"})
    IO ()

-- | Sets the media format used in the profile.
encodingProfileSetFormat ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> Gst.Caps.Caps
    -- ^ /@format@/: the media format to use in the profile.
    -> m ()
encodingProfileSetFormat :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> Caps -> m ()
encodingProfileSetFormat a
profile Caps
format = 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
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    Ptr Caps
format' <- Caps -> IO (Ptr Caps)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Caps
format
    Ptr EncodingProfile -> Ptr Caps -> IO ()
gst_encoding_profile_set_format Ptr EncodingProfile
profile' Ptr Caps
format'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    Caps -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Caps
format
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EncodingProfileSetFormatMethodInfo
instance (signature ~ (Gst.Caps.Caps -> m ()), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileSetFormatMethodInfo a signature where
    overloadedMethod = encodingProfileSetFormat

instance O.OverloadedMethodInfo EncodingProfileSetFormatMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileSetFormat",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileSetFormat"
        })


#endif

-- method EncodingProfile::set_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name to set on the profile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_set_name" gst_encoding_profile_set_name :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    CString ->                              -- name : TBasicType TUTF8
    IO ()

-- | Set /@name@/ as the given name for the /@profile@/. A copy of /@name@/ will be made
-- internally.
encodingProfileSetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> Maybe (T.Text)
    -- ^ /@name@/: the name to set on the profile
    -> m ()
encodingProfileSetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> Maybe Text -> m ()
encodingProfileSetName a
profile Maybe Text
name = 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
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    CString
maybeName <- case Maybe Text
name of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jName -> do
            CString
jName' <- Text -> IO CString
textToCString Text
jName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jName'
    Ptr EncodingProfile -> CString -> IO ()
gst_encoding_profile_set_name Ptr EncodingProfile
profile' CString
maybeName
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeName
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EncodingProfileSetNameMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileSetNameMethodInfo a signature where
    overloadedMethod = encodingProfileSetName

instance O.OverloadedMethodInfo EncodingProfileSetNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileSetName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileSetName"
        })


#endif

-- method EncodingProfile::set_presence
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "presence"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of time the profile can be used"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_set_presence" gst_encoding_profile_set_presence :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    Word32 ->                               -- presence : TBasicType TUInt
    IO ()

-- | Set the number of time the profile is used in its parent
-- container profile. If 0, it is not a mandatory stream
encodingProfileSetPresence ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> Word32
    -- ^ /@presence@/: the number of time the profile can be used
    -> m ()
encodingProfileSetPresence :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> Word32 -> m ()
encodingProfileSetPresence a
profile Word32
presence = 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
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    Ptr EncodingProfile -> Word32 -> IO ()
gst_encoding_profile_set_presence Ptr EncodingProfile
profile' Word32
presence
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EncodingProfileSetPresenceMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileSetPresenceMethodInfo a signature where
    overloadedMethod = encodingProfileSetPresence

instance O.OverloadedMethodInfo EncodingProfileSetPresenceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileSetPresence",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileSetPresence"
        })


#endif

-- method EncodingProfile::set_preset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "preset"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the element preset to use"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_set_preset" gst_encoding_profile_set_preset :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    CString ->                              -- preset : TBasicType TUTF8
    IO ()

-- | Sets the name of the t'GI.Gst.Objects.Element.Element' that implements the t'GI.Gst.Interfaces.Preset.Preset' interface
-- to use for the profile.
-- This is the name that has been set when saving the preset.
encodingProfileSetPreset ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> Maybe (T.Text)
    -- ^ /@preset@/: the element preset to use
    -> m ()
encodingProfileSetPreset :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> Maybe Text -> m ()
encodingProfileSetPreset a
profile Maybe Text
preset = 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
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    CString
maybePreset <- case Maybe Text
preset of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jPreset -> do
            CString
jPreset' <- Text -> IO CString
textToCString Text
jPreset
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jPreset'
    Ptr EncodingProfile -> CString -> IO ()
gst_encoding_profile_set_preset Ptr EncodingProfile
profile' CString
maybePreset
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybePreset
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EncodingProfileSetPresetMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileSetPresetMethodInfo a signature where
    overloadedMethod = encodingProfileSetPreset

instance O.OverloadedMethodInfo EncodingProfileSetPresetMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileSetPreset",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileSetPreset"
        })


#endif

-- method EncodingProfile::set_preset_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "preset_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The name of the preset to use in this @profile."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_set_preset_name" gst_encoding_profile_set_preset_name :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    CString ->                              -- preset_name : TBasicType TUTF8
    IO ()

-- | Sets the name of the t'GI.Gst.Interfaces.Preset.Preset'\'s factory to be used in the profile.
encodingProfileSetPresetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> Maybe (T.Text)
    -- ^ /@presetName@/: The name of the preset to use in this /@profile@/.
    -> m ()
encodingProfileSetPresetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> Maybe Text -> m ()
encodingProfileSetPresetName a
profile Maybe Text
presetName = 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
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    CString
maybePresetName <- case Maybe Text
presetName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jPresetName -> do
            CString
jPresetName' <- Text -> IO CString
textToCString Text
jPresetName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jPresetName'
    Ptr EncodingProfile -> CString -> IO ()
gst_encoding_profile_set_preset_name Ptr EncodingProfile
profile' CString
maybePresetName
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybePresetName
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EncodingProfileSetPresetNameMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileSetPresetNameMethodInfo a signature where
    overloadedMethod = encodingProfileSetPresetName

instance O.OverloadedMethodInfo EncodingProfileSetPresetNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileSetPresetName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileSetPresetName"
        })


#endif

-- method EncodingProfile::set_restriction
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "restriction"
--           , argType = TInterface Name { namespace = "Gst" , name = "Caps" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the restriction to apply"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_set_restriction" gst_encoding_profile_set_restriction :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    Ptr Gst.Caps.Caps ->                    -- restriction : TInterface (Name {namespace = "Gst", name = "Caps"})
    IO ()

-- | Set the restriction t'GI.Gst.Structs.Caps.Caps' to apply before the encoder
-- that will be used in the profile. See 'GI.GstPbutils.Objects.EncodingProfile.encodingProfileGetRestriction'
-- for more about restrictions. Does not apply to t'GI.GstPbutils.Objects.EncodingContainerProfile.EncodingContainerProfile'.
encodingProfileSetRestriction ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> Maybe (Gst.Caps.Caps)
    -- ^ /@restriction@/: the restriction to apply
    -> m ()
encodingProfileSetRestriction :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> Maybe Caps -> m ()
encodingProfileSetRestriction a
profile Maybe Caps
restriction = 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
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    Ptr Caps
maybeRestriction <- case Maybe Caps
restriction of
        Maybe Caps
Nothing -> Ptr Caps -> IO (Ptr Caps)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Caps
forall a. Ptr a
nullPtr
        Just Caps
jRestriction -> do
            Ptr Caps
jRestriction' <- Caps -> IO (Ptr Caps)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Caps
jRestriction
            Ptr Caps -> IO (Ptr Caps)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Caps
jRestriction'
    Ptr EncodingProfile -> Ptr Caps -> IO ()
gst_encoding_profile_set_restriction Ptr EncodingProfile
profile' Ptr Caps
maybeRestriction
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    Maybe Caps -> (Caps -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Caps
restriction Caps -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EncodingProfileSetRestrictionMethodInfo
instance (signature ~ (Maybe (Gst.Caps.Caps) -> m ()), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileSetRestrictionMethodInfo a signature where
    overloadedMethod = encodingProfileSetRestriction

instance O.OverloadedMethodInfo EncodingProfileSetRestrictionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileSetRestriction",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileSetRestriction"
        })


#endif

-- method EncodingProfile::set_single_segment
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "profile"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "EncodingProfile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstEncodingProfile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "single_segment"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "#TRUE if the stream represented by @profile should use a\nsingle segment before the encoder, #FALSE otherwise."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_set_single_segment" gst_encoding_profile_set_single_segment :: 
    Ptr EncodingProfile ->                  -- profile : TInterface (Name {namespace = "GstPbutils", name = "EncodingProfile"})
    CInt ->                                 -- single_segment : TBasicType TBoolean
    IO ()

-- | If using a single segment, buffers will be retimestamped and segments will be
-- eat so as to appear as one segment.
-- 
-- > *NOTE*: Single segment is not property supported when using
-- > @/encodebin:avoid-reencoding/@
-- 
-- /Since: 1.18/
encodingProfileSetSingleSegment ::
    (B.CallStack.HasCallStack, MonadIO m, IsEncodingProfile a) =>
    a
    -- ^ /@profile@/: a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile'
    -> Bool
    -- ^ /@singleSegment@/: @/TRUE/@ if the stream represented by /@profile@/ should use a
    -- single segment before the encoder, @/FALSE/@ otherwise.
    -> m ()
encodingProfileSetSingleSegment :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEncodingProfile a) =>
a -> Bool -> m ()
encodingProfileSetSingleSegment a
profile Bool
singleSegment = 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
$ do
    Ptr EncodingProfile
profile' <- a -> IO (Ptr EncodingProfile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
profile
    let singleSegment' :: CInt
singleSegment' = (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
singleSegment
    Ptr EncodingProfile -> CInt -> IO ()
gst_encoding_profile_set_single_segment Ptr EncodingProfile
profile' CInt
singleSegment'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
profile
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EncodingProfileSetSingleSegmentMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsEncodingProfile a) => O.OverloadedMethod EncodingProfileSetSingleSegmentMethodInfo a signature where
    overloadedMethod = encodingProfileSetSingleSegment

instance O.OverloadedMethodInfo EncodingProfileSetSingleSegmentMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GstPbutils.Objects.EncodingProfile.encodingProfileSetSingleSegment",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gstpbutils-1.0.27/docs/GI-GstPbutils-Objects-EncodingProfile.html#v:encodingProfileSetSingleSegment"
        })


#endif

-- method EncodingProfile::find
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "targetname"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The name of the target"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "profilename"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The name of the profile, if %NULL\nprovided, it will default to the encoding profile called `default`."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "category"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The target category. Can be %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "GstPbutils" , name = "EncodingProfile" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_find" gst_encoding_profile_find :: 
    CString ->                              -- targetname : TBasicType TUTF8
    CString ->                              -- profilename : TBasicType TUTF8
    CString ->                              -- category : TBasicType TUTF8
    IO (Ptr EncodingProfile)

-- | Find the t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile' with the specified name and category.
encodingProfileFind ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@targetname@/: The name of the target
    -> Maybe (T.Text)
    -- ^ /@profilename@/: The name of the profile, if 'P.Nothing'
    -- provided, it will default to the encoding profile called @default@.
    -> Maybe (T.Text)
    -- ^ /@category@/: The target category. Can be 'P.Nothing'
    -> m (Maybe EncodingProfile)
    -- ^ __Returns:__ The matching t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile' or 'P.Nothing'.
encodingProfileFind :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Maybe Text -> Maybe Text -> m (Maybe EncodingProfile)
encodingProfileFind Text
targetname Maybe Text
profilename Maybe Text
category = IO (Maybe EncodingProfile) -> m (Maybe EncodingProfile)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe EncodingProfile) -> m (Maybe EncodingProfile))
-> IO (Maybe EncodingProfile) -> m (Maybe EncodingProfile)
forall a b. (a -> b) -> a -> b
$ do
    CString
targetname' <- Text -> IO CString
textToCString Text
targetname
    CString
maybeProfilename <- case Maybe Text
profilename of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jProfilename -> do
            CString
jProfilename' <- Text -> IO CString
textToCString Text
jProfilename
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jProfilename'
    CString
maybeCategory <- case Maybe Text
category of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jCategory -> do
            CString
jCategory' <- Text -> IO CString
textToCString Text
jCategory
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jCategory'
    Ptr EncodingProfile
result <- CString -> CString -> CString -> IO (Ptr EncodingProfile)
gst_encoding_profile_find CString
targetname' CString
maybeProfilename CString
maybeCategory
    Maybe EncodingProfile
maybeResult <- Ptr EncodingProfile
-> (Ptr EncodingProfile -> IO EncodingProfile)
-> IO (Maybe EncodingProfile)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr EncodingProfile
result ((Ptr EncodingProfile -> IO EncodingProfile)
 -> IO (Maybe EncodingProfile))
-> (Ptr EncodingProfile -> IO EncodingProfile)
-> IO (Maybe EncodingProfile)
forall a b. (a -> b) -> a -> b
$ \Ptr EncodingProfile
result' -> do
        EncodingProfile
result'' <- ((ManagedPtr EncodingProfile -> EncodingProfile)
-> Ptr EncodingProfile -> IO EncodingProfile
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr EncodingProfile -> EncodingProfile
EncodingProfile) Ptr EncodingProfile
result'
        EncodingProfile -> IO EncodingProfile
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return EncodingProfile
result''
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
targetname'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeProfilename
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeCategory
    Maybe EncodingProfile -> IO (Maybe EncodingProfile)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe EncodingProfile
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method EncodingProfile::from_discoverer
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface
--                 Name { namespace = "GstPbutils" , name = "DiscovererInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GstDiscovererInfo to read from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "GstPbutils" , name = "EncodingProfile" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_encoding_profile_from_discoverer" gst_encoding_profile_from_discoverer :: 
    Ptr GstPbutils.DiscovererInfo.DiscovererInfo -> -- info : TInterface (Name {namespace = "GstPbutils", name = "DiscovererInfo"})
    IO (Ptr EncodingProfile)

-- | Creates a t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile' matching the formats from the given
-- t'GI.GstPbutils.Objects.DiscovererInfo.DiscovererInfo'. Streams other than audio or video (eg,
-- subtitles), are currently ignored.
encodingProfileFromDiscoverer ::
    (B.CallStack.HasCallStack, MonadIO m, GstPbutils.DiscovererInfo.IsDiscovererInfo a) =>
    a
    -- ^ /@info@/: The t'GI.GstPbutils.Objects.DiscovererInfo.DiscovererInfo' to read from
    -> m (Maybe EncodingProfile)
    -- ^ __Returns:__ The new t'GI.GstPbutils.Objects.EncodingProfile.EncodingProfile' or 'P.Nothing'.
encodingProfileFromDiscoverer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDiscovererInfo a) =>
a -> m (Maybe EncodingProfile)
encodingProfileFromDiscoverer a
info = IO (Maybe EncodingProfile) -> m (Maybe EncodingProfile)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe EncodingProfile) -> m (Maybe EncodingProfile))
-> IO (Maybe EncodingProfile) -> m (Maybe EncodingProfile)
forall a b. (a -> b) -> a -> b
$ do
    Ptr DiscovererInfo
info' <- a -> IO (Ptr DiscovererInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Ptr EncodingProfile
result <- Ptr DiscovererInfo -> IO (Ptr EncodingProfile)
gst_encoding_profile_from_discoverer Ptr DiscovererInfo
info'
    Maybe EncodingProfile
maybeResult <- Ptr EncodingProfile
-> (Ptr EncodingProfile -> IO EncodingProfile)
-> IO (Maybe EncodingProfile)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr EncodingProfile
result ((Ptr EncodingProfile -> IO EncodingProfile)
 -> IO (Maybe EncodingProfile))
-> (Ptr EncodingProfile -> IO EncodingProfile)
-> IO (Maybe EncodingProfile)
forall a b. (a -> b) -> a -> b
$ \Ptr EncodingProfile
result' -> do
        EncodingProfile
result'' <- ((ManagedPtr EncodingProfile -> EncodingProfile)
-> Ptr EncodingProfile -> IO EncodingProfile
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr EncodingProfile -> EncodingProfile
EncodingProfile) Ptr EncodingProfile
result'
        EncodingProfile -> IO EncodingProfile
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return EncodingProfile
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Maybe EncodingProfile -> IO (Maybe EncodingProfile)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe EncodingProfile
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif