{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- GhostPads are useful when organizing pipelines with t'GI.Gst.Objects.Bin.Bin' like elements.
-- The idea here is to create hierarchical element graphs. The bin element
-- contains a sub-graph. Now one would like to treat the bin-element like any
-- other t'GI.Gst.Objects.Element.Element'. This is where GhostPads come into play. A GhostPad acts as
-- a proxy for another pad. Thus the bin can have sink and source ghost-pads
-- that are associated with sink and source pads of the child elements.
-- 
-- If the target pad is known at creation time, 'GI.Gst.Objects.GhostPad.ghostPadNew' is the
-- function to use to get a ghost-pad. Otherwise one can use 'GI.Gst.Objects.GhostPad.ghostPadNewNoTarget'
-- to create the ghost-pad and use 'GI.Gst.Objects.GhostPad.ghostPadSetTarget' to establish the
-- association later on.
-- 
-- Note that GhostPads add overhead to the data processing of a pipeline.

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

module GI.Gst.Objects.GhostPad
    ( 

-- * Exported types
    GhostPad(..)                            ,
    IsGhostPad                              ,
    toGhostPad                              ,
    noGhostPad                              ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveGhostPadMethod                   ,
#endif


-- ** activateModeDefault #method:activateModeDefault#

    ghostPadActivateModeDefault             ,


-- ** construct #method:construct#

#if defined(ENABLE_OVERLOADING)
    GhostPadConstructMethodInfo             ,
#endif
    ghostPadConstruct                       ,


-- ** getTarget #method:getTarget#

#if defined(ENABLE_OVERLOADING)
    GhostPadGetTargetMethodInfo             ,
#endif
    ghostPadGetTarget                       ,


-- ** internalActivateModeDefault #method:internalActivateModeDefault#

    ghostPadInternalActivateModeDefault     ,


-- ** new #method:new#

    ghostPadNew                             ,


-- ** newFromTemplate #method:newFromTemplate#

    ghostPadNewFromTemplate                 ,


-- ** newNoTarget #method:newNoTarget#

    ghostPadNewNoTarget                     ,


-- ** newNoTargetFromTemplate #method:newNoTargetFromTemplate#

    ghostPadNewNoTargetFromTemplate         ,


-- ** setTarget #method:setTarget#

#if defined(ENABLE_OVERLOADING)
    GhostPadSetTargetMethodInfo             ,
#endif
    ghostPadSetTarget                       ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gst.Enums as Gst.Enums
import {-# SOURCE #-} qualified GI.Gst.Objects.Object as Gst.Object
import {-# SOURCE #-} qualified GI.Gst.Objects.Pad as Gst.Pad
import {-# SOURCE #-} qualified GI.Gst.Objects.PadTemplate as Gst.PadTemplate
import {-# SOURCE #-} qualified GI.Gst.Objects.ProxyPad as Gst.ProxyPad

-- | Memory-managed wrapper type.
newtype GhostPad = GhostPad (ManagedPtr GhostPad)
    deriving (GhostPad -> GhostPad -> Bool
(GhostPad -> GhostPad -> Bool)
-> (GhostPad -> GhostPad -> Bool) -> Eq GhostPad
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GhostPad -> GhostPad -> Bool
$c/= :: GhostPad -> GhostPad -> Bool
== :: GhostPad -> GhostPad -> Bool
$c== :: GhostPad -> GhostPad -> Bool
Eq)
foreign import ccall "gst_ghost_pad_get_type"
    c_gst_ghost_pad_get_type :: IO GType

instance GObject GhostPad where
    gobjectType :: IO GType
gobjectType = IO GType
c_gst_ghost_pad_get_type
    

-- | Convert 'GhostPad' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue GhostPad where
    toGValue :: GhostPad -> IO GValue
toGValue o :: GhostPad
o = do
        GType
gtype <- IO GType
c_gst_ghost_pad_get_type
        GhostPad -> (Ptr GhostPad -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr GhostPad
o (GType
-> (GValue -> Ptr GhostPad -> IO ()) -> Ptr GhostPad -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr GhostPad -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO GhostPad
fromGValue gv :: GValue
gv = do
        Ptr GhostPad
ptr <- GValue -> IO (Ptr GhostPad)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr GhostPad)
        (ManagedPtr GhostPad -> GhostPad) -> Ptr GhostPad -> IO GhostPad
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr GhostPad -> GhostPad
GhostPad Ptr GhostPad
ptr
        
    

-- | Type class for types which can be safely cast to `GhostPad`, for instance with `toGhostPad`.
class (GObject o, O.IsDescendantOf GhostPad o) => IsGhostPad o
instance (GObject o, O.IsDescendantOf GhostPad o) => IsGhostPad o

instance O.HasParentTypes GhostPad
type instance O.ParentTypes GhostPad = '[Gst.ProxyPad.ProxyPad, Gst.Pad.Pad, Gst.Object.Object, GObject.Object.Object]

-- | Cast to `GhostPad`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toGhostPad :: (MonadIO m, IsGhostPad o) => o -> m GhostPad
toGhostPad :: o -> m GhostPad
toGhostPad = IO GhostPad -> m GhostPad
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GhostPad -> m GhostPad)
-> (o -> IO GhostPad) -> o -> m GhostPad
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr GhostPad -> GhostPad) -> o -> IO GhostPad
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr GhostPad -> GhostPad
GhostPad

-- | A convenience alias for `Nothing` :: `Maybe` `GhostPad`.
noGhostPad :: Maybe GhostPad
noGhostPad :: Maybe GhostPad
noGhostPad = Maybe GhostPad
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveGhostPadMethod (t :: Symbol) (o :: *) :: * where
    ResolveGhostPadMethod "activateMode" o = Gst.Pad.PadActivateModeMethodInfo
    ResolveGhostPadMethod "addControlBinding" o = Gst.Object.ObjectAddControlBindingMethodInfo
    ResolveGhostPadMethod "addProbe" o = Gst.Pad.PadAddProbeMethodInfo
    ResolveGhostPadMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveGhostPadMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveGhostPadMethod "canLink" o = Gst.Pad.PadCanLinkMethodInfo
    ResolveGhostPadMethod "chain" o = Gst.Pad.PadChainMethodInfo
    ResolveGhostPadMethod "chainList" o = Gst.Pad.PadChainListMethodInfo
    ResolveGhostPadMethod "checkReconfigure" o = Gst.Pad.PadCheckReconfigureMethodInfo
    ResolveGhostPadMethod "construct" o = GhostPadConstructMethodInfo
    ResolveGhostPadMethod "createStreamId" o = Gst.Pad.PadCreateStreamIdMethodInfo
    ResolveGhostPadMethod "defaultError" o = Gst.Object.ObjectDefaultErrorMethodInfo
    ResolveGhostPadMethod "eventDefault" o = Gst.Pad.PadEventDefaultMethodInfo
    ResolveGhostPadMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveGhostPadMethod "forward" o = Gst.Pad.PadForwardMethodInfo
    ResolveGhostPadMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveGhostPadMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveGhostPadMethod "hasActiveControlBindings" o = Gst.Object.ObjectHasActiveControlBindingsMethodInfo
    ResolveGhostPadMethod "hasAncestor" o = Gst.Object.ObjectHasAncestorMethodInfo
    ResolveGhostPadMethod "hasAsAncestor" o = Gst.Object.ObjectHasAsAncestorMethodInfo
    ResolveGhostPadMethod "hasAsParent" o = Gst.Object.ObjectHasAsParentMethodInfo
    ResolveGhostPadMethod "hasCurrentCaps" o = Gst.Pad.PadHasCurrentCapsMethodInfo
    ResolveGhostPadMethod "isActive" o = Gst.Pad.PadIsActiveMethodInfo
    ResolveGhostPadMethod "isBlocked" o = Gst.Pad.PadIsBlockedMethodInfo
    ResolveGhostPadMethod "isBlocking" o = Gst.Pad.PadIsBlockingMethodInfo
    ResolveGhostPadMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveGhostPadMethod "isLinked" o = Gst.Pad.PadIsLinkedMethodInfo
    ResolveGhostPadMethod "iterateInternalLinks" o = Gst.Pad.PadIterateInternalLinksMethodInfo
    ResolveGhostPadMethod "link" o = Gst.Pad.PadLinkMethodInfo
    ResolveGhostPadMethod "linkFull" o = Gst.Pad.PadLinkFullMethodInfo
    ResolveGhostPadMethod "linkMaybeGhosting" o = Gst.Pad.PadLinkMaybeGhostingMethodInfo
    ResolveGhostPadMethod "linkMaybeGhostingFull" o = Gst.Pad.PadLinkMaybeGhostingFullMethodInfo
    ResolveGhostPadMethod "markReconfigure" o = Gst.Pad.PadMarkReconfigureMethodInfo
    ResolveGhostPadMethod "needsReconfigure" o = Gst.Pad.PadNeedsReconfigureMethodInfo
    ResolveGhostPadMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveGhostPadMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveGhostPadMethod "pauseTask" o = Gst.Pad.PadPauseTaskMethodInfo
    ResolveGhostPadMethod "peerQuery" o = Gst.Pad.PadPeerQueryMethodInfo
    ResolveGhostPadMethod "peerQueryAcceptCaps" o = Gst.Pad.PadPeerQueryAcceptCapsMethodInfo
    ResolveGhostPadMethod "peerQueryCaps" o = Gst.Pad.PadPeerQueryCapsMethodInfo
    ResolveGhostPadMethod "peerQueryConvert" o = Gst.Pad.PadPeerQueryConvertMethodInfo
    ResolveGhostPadMethod "peerQueryDuration" o = Gst.Pad.PadPeerQueryDurationMethodInfo
    ResolveGhostPadMethod "peerQueryPosition" o = Gst.Pad.PadPeerQueryPositionMethodInfo
    ResolveGhostPadMethod "proxyQueryAcceptCaps" o = Gst.Pad.PadProxyQueryAcceptCapsMethodInfo
    ResolveGhostPadMethod "proxyQueryCaps" o = Gst.Pad.PadProxyQueryCapsMethodInfo
    ResolveGhostPadMethod "pullRange" o = Gst.Pad.PadPullRangeMethodInfo
    ResolveGhostPadMethod "push" o = Gst.Pad.PadPushMethodInfo
    ResolveGhostPadMethod "pushEvent" o = Gst.Pad.PadPushEventMethodInfo
    ResolveGhostPadMethod "pushList" o = Gst.Pad.PadPushListMethodInfo
    ResolveGhostPadMethod "query" o = Gst.Pad.PadQueryMethodInfo
    ResolveGhostPadMethod "queryAcceptCaps" o = Gst.Pad.PadQueryAcceptCapsMethodInfo
    ResolveGhostPadMethod "queryCaps" o = Gst.Pad.PadQueryCapsMethodInfo
    ResolveGhostPadMethod "queryConvert" o = Gst.Pad.PadQueryConvertMethodInfo
    ResolveGhostPadMethod "queryDefault" o = Gst.Pad.PadQueryDefaultMethodInfo
    ResolveGhostPadMethod "queryDuration" o = Gst.Pad.PadQueryDurationMethodInfo
    ResolveGhostPadMethod "queryPosition" o = Gst.Pad.PadQueryPositionMethodInfo
    ResolveGhostPadMethod "ref" o = Gst.Object.ObjectRefMethodInfo
    ResolveGhostPadMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveGhostPadMethod "removeControlBinding" o = Gst.Object.ObjectRemoveControlBindingMethodInfo
    ResolveGhostPadMethod "removeProbe" o = Gst.Pad.PadRemoveProbeMethodInfo
    ResolveGhostPadMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveGhostPadMethod "sendEvent" o = Gst.Pad.PadSendEventMethodInfo
    ResolveGhostPadMethod "startTask" o = Gst.Pad.PadStartTaskMethodInfo
    ResolveGhostPadMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveGhostPadMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveGhostPadMethod "stickyEventsForeach" o = Gst.Pad.PadStickyEventsForeachMethodInfo
    ResolveGhostPadMethod "stopTask" o = Gst.Pad.PadStopTaskMethodInfo
    ResolveGhostPadMethod "storeStickyEvent" o = Gst.Pad.PadStoreStickyEventMethodInfo
    ResolveGhostPadMethod "suggestNextSync" o = Gst.Object.ObjectSuggestNextSyncMethodInfo
    ResolveGhostPadMethod "syncValues" o = Gst.Object.ObjectSyncValuesMethodInfo
    ResolveGhostPadMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveGhostPadMethod "unlink" o = Gst.Pad.PadUnlinkMethodInfo
    ResolveGhostPadMethod "unparent" o = Gst.Object.ObjectUnparentMethodInfo
    ResolveGhostPadMethod "unref" o = Gst.Object.ObjectUnrefMethodInfo
    ResolveGhostPadMethod "useFixedCaps" o = Gst.Pad.PadUseFixedCapsMethodInfo
    ResolveGhostPadMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveGhostPadMethod "getAllowedCaps" o = Gst.Pad.PadGetAllowedCapsMethodInfo
    ResolveGhostPadMethod "getControlBinding" o = Gst.Object.ObjectGetControlBindingMethodInfo
    ResolveGhostPadMethod "getControlRate" o = Gst.Object.ObjectGetControlRateMethodInfo
    ResolveGhostPadMethod "getCurrentCaps" o = Gst.Pad.PadGetCurrentCapsMethodInfo
    ResolveGhostPadMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveGhostPadMethod "getDirection" o = Gst.Pad.PadGetDirectionMethodInfo
    ResolveGhostPadMethod "getElementPrivate" o = Gst.Pad.PadGetElementPrivateMethodInfo
    ResolveGhostPadMethod "getGValueArray" o = Gst.Object.ObjectGetGValueArrayMethodInfo
    ResolveGhostPadMethod "getInternal" o = Gst.ProxyPad.ProxyPadGetInternalMethodInfo
    ResolveGhostPadMethod "getLastFlowReturn" o = Gst.Pad.PadGetLastFlowReturnMethodInfo
    ResolveGhostPadMethod "getName" o = Gst.Object.ObjectGetNameMethodInfo
    ResolveGhostPadMethod "getOffset" o = Gst.Pad.PadGetOffsetMethodInfo
    ResolveGhostPadMethod "getPadTemplate" o = Gst.Pad.PadGetPadTemplateMethodInfo
    ResolveGhostPadMethod "getPadTemplateCaps" o = Gst.Pad.PadGetPadTemplateCapsMethodInfo
    ResolveGhostPadMethod "getParent" o = Gst.Object.ObjectGetParentMethodInfo
    ResolveGhostPadMethod "getParentElement" o = Gst.Pad.PadGetParentElementMethodInfo
    ResolveGhostPadMethod "getPathString" o = Gst.Object.ObjectGetPathStringMethodInfo
    ResolveGhostPadMethod "getPeer" o = Gst.Pad.PadGetPeerMethodInfo
    ResolveGhostPadMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveGhostPadMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveGhostPadMethod "getRange" o = Gst.Pad.PadGetRangeMethodInfo
    ResolveGhostPadMethod "getStickyEvent" o = Gst.Pad.PadGetStickyEventMethodInfo
    ResolveGhostPadMethod "getStream" o = Gst.Pad.PadGetStreamMethodInfo
    ResolveGhostPadMethod "getStreamId" o = Gst.Pad.PadGetStreamIdMethodInfo
    ResolveGhostPadMethod "getTarget" o = GhostPadGetTargetMethodInfo
    ResolveGhostPadMethod "getTaskState" o = Gst.Pad.PadGetTaskStateMethodInfo
    ResolveGhostPadMethod "getValue" o = Gst.Object.ObjectGetValueMethodInfo
    ResolveGhostPadMethod "setActivateFunctionFull" o = Gst.Pad.PadSetActivateFunctionFullMethodInfo
    ResolveGhostPadMethod "setActivatemodeFunctionFull" o = Gst.Pad.PadSetActivatemodeFunctionFullMethodInfo
    ResolveGhostPadMethod "setActive" o = Gst.Pad.PadSetActiveMethodInfo
    ResolveGhostPadMethod "setChainFunctionFull" o = Gst.Pad.PadSetChainFunctionFullMethodInfo
    ResolveGhostPadMethod "setChainListFunctionFull" o = Gst.Pad.PadSetChainListFunctionFullMethodInfo
    ResolveGhostPadMethod "setControlBindingDisabled" o = Gst.Object.ObjectSetControlBindingDisabledMethodInfo
    ResolveGhostPadMethod "setControlBindingsDisabled" o = Gst.Object.ObjectSetControlBindingsDisabledMethodInfo
    ResolveGhostPadMethod "setControlRate" o = Gst.Object.ObjectSetControlRateMethodInfo
    ResolveGhostPadMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveGhostPadMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveGhostPadMethod "setElementPrivate" o = Gst.Pad.PadSetElementPrivateMethodInfo
    ResolveGhostPadMethod "setEventFullFunctionFull" o = Gst.Pad.PadSetEventFullFunctionFullMethodInfo
    ResolveGhostPadMethod "setEventFunctionFull" o = Gst.Pad.PadSetEventFunctionFullMethodInfo
    ResolveGhostPadMethod "setGetrangeFunctionFull" o = Gst.Pad.PadSetGetrangeFunctionFullMethodInfo
    ResolveGhostPadMethod "setIterateInternalLinksFunctionFull" o = Gst.Pad.PadSetIterateInternalLinksFunctionFullMethodInfo
    ResolveGhostPadMethod "setLinkFunctionFull" o = Gst.Pad.PadSetLinkFunctionFullMethodInfo
    ResolveGhostPadMethod "setName" o = Gst.Object.ObjectSetNameMethodInfo
    ResolveGhostPadMethod "setOffset" o = Gst.Pad.PadSetOffsetMethodInfo
    ResolveGhostPadMethod "setParent" o = Gst.Object.ObjectSetParentMethodInfo
    ResolveGhostPadMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveGhostPadMethod "setQueryFunctionFull" o = Gst.Pad.PadSetQueryFunctionFullMethodInfo
    ResolveGhostPadMethod "setTarget" o = GhostPadSetTargetMethodInfo
    ResolveGhostPadMethod "setUnlinkFunctionFull" o = Gst.Pad.PadSetUnlinkFunctionFullMethodInfo
    ResolveGhostPadMethod l o = O.MethodResolutionFailed l o

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

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GhostPad
type instance O.AttributeList GhostPad = GhostPadAttributeList
type GhostPadAttributeList = ('[ '("caps", Gst.Pad.PadCapsPropertyInfo), '("direction", Gst.Pad.PadDirectionPropertyInfo), '("name", Gst.Object.ObjectNamePropertyInfo), '("offset", Gst.Pad.PadOffsetPropertyInfo), '("parent", Gst.Object.ObjectParentPropertyInfo), '("template", Gst.Pad.PadTemplatePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList GhostPad = GhostPadSignalList
type GhostPadSignalList = ('[ '("deepNotify", Gst.Object.ObjectDeepNotifySignalInfo), '("linked", Gst.Pad.PadLinkedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("unlinked", Gst.Pad.PadUnlinkedSignalInfo)] :: [(Symbol, *)])

#endif

-- method GhostPad::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the name of the new pad, or %NULL to assign a default name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target"
--           , argType = TInterface Name { namespace = "Gst" , name = "Pad" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the pad to ghost." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "GhostPad" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_ghost_pad_new" gst_ghost_pad_new :: 
    CString ->                              -- name : TBasicType TUTF8
    Ptr Gst.Pad.Pad ->                      -- target : TInterface (Name {namespace = "Gst", name = "Pad"})
    IO (Ptr GhostPad)

-- | Create a new ghostpad with /@target@/ as the target. The direction will be taken
-- from the target pad. /@target@/ must be unlinked.
-- 
-- Will ref the target.
ghostPadNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gst.Pad.IsPad a) =>
    Maybe (T.Text)
    -- ^ /@name@/: the name of the new pad, or 'P.Nothing' to assign a default name
    -> a
    -- ^ /@target@/: the pad to ghost.
    -> m (Maybe GhostPad)
    -- ^ __Returns:__ a new t'GI.Gst.Objects.Pad.Pad', or 'P.Nothing' in
    -- case of an error.
ghostPadNew :: Maybe Text -> a -> m (Maybe GhostPad)
ghostPadNew name :: Maybe Text
name target :: a
target = IO (Maybe GhostPad) -> m (Maybe GhostPad)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GhostPad) -> m (Maybe GhostPad))
-> IO (Maybe GhostPad) -> m (Maybe GhostPad)
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
maybeName <- case Maybe Text
name of
        Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just jName :: Text
jName -> do
            Ptr CChar
jName' <- Text -> IO (Ptr CChar)
textToCString Text
jName
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jName'
    Ptr Pad
target' <- a -> IO (Ptr Pad)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
target
    Ptr GhostPad
result <- Ptr CChar -> Ptr Pad -> IO (Ptr GhostPad)
gst_ghost_pad_new Ptr CChar
maybeName Ptr Pad
target'
    Maybe GhostPad
maybeResult <- Ptr GhostPad
-> (Ptr GhostPad -> IO GhostPad) -> IO (Maybe GhostPad)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GhostPad
result ((Ptr GhostPad -> IO GhostPad) -> IO (Maybe GhostPad))
-> (Ptr GhostPad -> IO GhostPad) -> IO (Maybe GhostPad)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr GhostPad
result' -> do
        GhostPad
result'' <- ((ManagedPtr GhostPad -> GhostPad) -> Ptr GhostPad -> IO GhostPad
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr GhostPad -> GhostPad
GhostPad) Ptr GhostPad
result'
        GhostPad -> IO GhostPad
forall (m :: * -> *) a. Monad m => a -> m a
return GhostPad
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
target
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeName
    Maybe GhostPad -> IO (Maybe GhostPad)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GhostPad
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method GhostPad::new_from_template
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the name of the new pad, or %NULL to assign a default name."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target"
--           , argType = TInterface Name { namespace = "Gst" , name = "Pad" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the pad to ghost." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "templ"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "PadTemplate" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GstPadTemplate to use on the ghostpad."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "GhostPad" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_ghost_pad_new_from_template" gst_ghost_pad_new_from_template :: 
    CString ->                              -- name : TBasicType TUTF8
    Ptr Gst.Pad.Pad ->                      -- target : TInterface (Name {namespace = "Gst", name = "Pad"})
    Ptr Gst.PadTemplate.PadTemplate ->      -- templ : TInterface (Name {namespace = "Gst", name = "PadTemplate"})
    IO (Ptr GhostPad)

-- | Create a new ghostpad with /@target@/ as the target. The direction will be taken
-- from the target pad. The template used on the ghostpad will be /@template@/.
-- 
-- Will ref the target.
ghostPadNewFromTemplate ::
    (B.CallStack.HasCallStack, MonadIO m, Gst.Pad.IsPad a, Gst.PadTemplate.IsPadTemplate b) =>
    Maybe (T.Text)
    -- ^ /@name@/: the name of the new pad, or 'P.Nothing' to assign a default name.
    -> a
    -- ^ /@target@/: the pad to ghost.
    -> b
    -- ^ /@templ@/: the t'GI.Gst.Objects.PadTemplate.PadTemplate' to use on the ghostpad.
    -> m (Maybe GhostPad)
    -- ^ __Returns:__ a new t'GI.Gst.Objects.Pad.Pad', or 'P.Nothing' in
    -- case of an error.
ghostPadNewFromTemplate :: Maybe Text -> a -> b -> m (Maybe GhostPad)
ghostPadNewFromTemplate name :: Maybe Text
name target :: a
target templ :: b
templ = IO (Maybe GhostPad) -> m (Maybe GhostPad)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GhostPad) -> m (Maybe GhostPad))
-> IO (Maybe GhostPad) -> m (Maybe GhostPad)
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
maybeName <- case Maybe Text
name of
        Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just jName :: Text
jName -> do
            Ptr CChar
jName' <- Text -> IO (Ptr CChar)
textToCString Text
jName
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jName'
    Ptr Pad
target' <- a -> IO (Ptr Pad)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
target
    Ptr PadTemplate
templ' <- b -> IO (Ptr PadTemplate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
templ
    Ptr GhostPad
result <- Ptr CChar -> Ptr Pad -> Ptr PadTemplate -> IO (Ptr GhostPad)
gst_ghost_pad_new_from_template Ptr CChar
maybeName Ptr Pad
target' Ptr PadTemplate
templ'
    Maybe GhostPad
maybeResult <- Ptr GhostPad
-> (Ptr GhostPad -> IO GhostPad) -> IO (Maybe GhostPad)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GhostPad
result ((Ptr GhostPad -> IO GhostPad) -> IO (Maybe GhostPad))
-> (Ptr GhostPad -> IO GhostPad) -> IO (Maybe GhostPad)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr GhostPad
result' -> do
        GhostPad
result'' <- ((ManagedPtr GhostPad -> GhostPad) -> Ptr GhostPad -> IO GhostPad
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr GhostPad -> GhostPad
GhostPad) Ptr GhostPad
result'
        GhostPad -> IO GhostPad
forall (m :: * -> *) a. Monad m => a -> m a
return GhostPad
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
target
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
templ
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeName
    Maybe GhostPad -> IO (Maybe GhostPad)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GhostPad
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method GhostPad::new_no_target
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the name of the new pad, or %NULL to assign a default name."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dir"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "PadDirection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the direction of the ghostpad"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "GhostPad" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_ghost_pad_new_no_target" gst_ghost_pad_new_no_target :: 
    CString ->                              -- name : TBasicType TUTF8
    CUInt ->                                -- dir : TInterface (Name {namespace = "Gst", name = "PadDirection"})
    IO (Ptr GhostPad)

-- | Create a new ghostpad without a target with the given direction.
-- A target can be set on the ghostpad later with the
-- 'GI.Gst.Objects.GhostPad.ghostPadSetTarget' function.
-- 
-- The created ghostpad will not have a padtemplate.
ghostPadNewNoTarget ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (T.Text)
    -- ^ /@name@/: the name of the new pad, or 'P.Nothing' to assign a default name.
    -> Gst.Enums.PadDirection
    -- ^ /@dir@/: the direction of the ghostpad
    -> m (Maybe GhostPad)
    -- ^ __Returns:__ a new t'GI.Gst.Objects.Pad.Pad', or 'P.Nothing' in
    -- case of an error.
ghostPadNewNoTarget :: Maybe Text -> PadDirection -> m (Maybe GhostPad)
ghostPadNewNoTarget name :: Maybe Text
name dir :: PadDirection
dir = IO (Maybe GhostPad) -> m (Maybe GhostPad)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GhostPad) -> m (Maybe GhostPad))
-> IO (Maybe GhostPad) -> m (Maybe GhostPad)
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
maybeName <- case Maybe Text
name of
        Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just jName :: Text
jName -> do
            Ptr CChar
jName' <- Text -> IO (Ptr CChar)
textToCString Text
jName
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jName'
    let dir' :: CUInt
dir' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PadDirection -> Int) -> PadDirection -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PadDirection -> Int
forall a. Enum a => a -> Int
fromEnum) PadDirection
dir
    Ptr GhostPad
result <- Ptr CChar -> CUInt -> IO (Ptr GhostPad)
gst_ghost_pad_new_no_target Ptr CChar
maybeName CUInt
dir'
    Maybe GhostPad
maybeResult <- Ptr GhostPad
-> (Ptr GhostPad -> IO GhostPad) -> IO (Maybe GhostPad)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GhostPad
result ((Ptr GhostPad -> IO GhostPad) -> IO (Maybe GhostPad))
-> (Ptr GhostPad -> IO GhostPad) -> IO (Maybe GhostPad)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr GhostPad
result' -> do
        GhostPad
result'' <- ((ManagedPtr GhostPad -> GhostPad) -> Ptr GhostPad -> IO GhostPad
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr GhostPad -> GhostPad
GhostPad) Ptr GhostPad
result'
        GhostPad -> IO GhostPad
forall (m :: * -> *) a. Monad m => a -> m a
return GhostPad
result''
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeName
    Maybe GhostPad -> IO (Maybe GhostPad)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GhostPad
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method GhostPad::new_no_target_from_template
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the name of the new pad, or %NULL to assign a default name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "templ"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "PadTemplate" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the #GstPadTemplate to create the ghostpad from."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "GhostPad" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_ghost_pad_new_no_target_from_template" gst_ghost_pad_new_no_target_from_template :: 
    CString ->                              -- name : TBasicType TUTF8
    Ptr Gst.PadTemplate.PadTemplate ->      -- templ : TInterface (Name {namespace = "Gst", name = "PadTemplate"})
    IO (Ptr GhostPad)

-- | Create a new ghostpad based on /@templ@/, without setting a target. The
-- direction will be taken from the /@templ@/.
ghostPadNewNoTargetFromTemplate ::
    (B.CallStack.HasCallStack, MonadIO m, Gst.PadTemplate.IsPadTemplate a) =>
    Maybe (T.Text)
    -- ^ /@name@/: the name of the new pad, or 'P.Nothing' to assign a default name
    -> a
    -- ^ /@templ@/: the t'GI.Gst.Objects.PadTemplate.PadTemplate' to create the ghostpad from.
    -> m (Maybe GhostPad)
    -- ^ __Returns:__ a new t'GI.Gst.Objects.Pad.Pad', or 'P.Nothing' in
    -- case of an error.
ghostPadNewNoTargetFromTemplate :: Maybe Text -> a -> m (Maybe GhostPad)
ghostPadNewNoTargetFromTemplate name :: Maybe Text
name templ :: a
templ = IO (Maybe GhostPad) -> m (Maybe GhostPad)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GhostPad) -> m (Maybe GhostPad))
-> IO (Maybe GhostPad) -> m (Maybe GhostPad)
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
maybeName <- case Maybe Text
name of
        Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just jName :: Text
jName -> do
            Ptr CChar
jName' <- Text -> IO (Ptr CChar)
textToCString Text
jName
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jName'
    Ptr PadTemplate
templ' <- a -> IO (Ptr PadTemplate)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
templ
    Ptr GhostPad
result <- Ptr CChar -> Ptr PadTemplate -> IO (Ptr GhostPad)
gst_ghost_pad_new_no_target_from_template Ptr CChar
maybeName Ptr PadTemplate
templ'
    Maybe GhostPad
maybeResult <- Ptr GhostPad
-> (Ptr GhostPad -> IO GhostPad) -> IO (Maybe GhostPad)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GhostPad
result ((Ptr GhostPad -> IO GhostPad) -> IO (Maybe GhostPad))
-> (Ptr GhostPad -> IO GhostPad) -> IO (Maybe GhostPad)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr GhostPad
result' -> do
        GhostPad
result'' <- ((ManagedPtr GhostPad -> GhostPad) -> Ptr GhostPad -> IO GhostPad
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr GhostPad -> GhostPad
GhostPad) Ptr GhostPad
result'
        GhostPad -> IO GhostPad
forall (m :: * -> *) a. Monad m => a -> m a
return GhostPad
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
templ
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeName
    Maybe GhostPad -> IO (Maybe GhostPad)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GhostPad
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method GhostPad::construct
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "gpad"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "GhostPad" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the newly allocated ghost pad"
--                 , 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_ghost_pad_construct" gst_ghost_pad_construct :: 
    Ptr GhostPad ->                         -- gpad : TInterface (Name {namespace = "Gst", name = "GhostPad"})
    IO CInt

-- | Finish initialization of a newly allocated ghost pad.
-- 
-- This function is most useful in language bindings and when subclassing
-- t'GI.Gst.Objects.GhostPad.GhostPad'; plugin and application developers normally will not call this
-- function. Call this function directly after a call to g_object_new
-- (GST_TYPE_GHOST_PAD, \"direction\", /@dir@/, ..., NULL).
ghostPadConstruct ::
    (B.CallStack.HasCallStack, MonadIO m, IsGhostPad a) =>
    a
    -- ^ /@gpad@/: the newly allocated ghost pad
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the construction succeeds, 'P.False' otherwise.
ghostPadConstruct :: a -> m Bool
ghostPadConstruct gpad :: a
gpad = IO Bool -> m Bool
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 GhostPad
gpad' <- a -> IO (Ptr GhostPad)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
gpad
    CInt
result <- Ptr GhostPad -> IO CInt
gst_ghost_pad_construct Ptr GhostPad
gpad'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
gpad
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data GhostPadConstructMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGhostPad a) => O.MethodInfo GhostPadConstructMethodInfo a signature where
    overloadedMethod = ghostPadConstruct

#endif

-- method GhostPad::get_target
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "gpad"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "GhostPad" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GstGhostPad" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Pad" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_ghost_pad_get_target" gst_ghost_pad_get_target :: 
    Ptr GhostPad ->                         -- gpad : TInterface (Name {namespace = "Gst", name = "GhostPad"})
    IO (Ptr Gst.Pad.Pad)

-- | Get the target pad of /@gpad@/. Unref target pad after usage.
ghostPadGetTarget ::
    (B.CallStack.HasCallStack, MonadIO m, IsGhostPad a) =>
    a
    -- ^ /@gpad@/: the t'GI.Gst.Objects.GhostPad.GhostPad'
    -> m (Maybe Gst.Pad.Pad)
    -- ^ __Returns:__ the target t'GI.Gst.Objects.Pad.Pad', can be
    -- 'P.Nothing' if the ghostpad has no target set. Unref target pad after
    -- usage.
ghostPadGetTarget :: a -> m (Maybe Pad)
ghostPadGetTarget gpad :: a
gpad = IO (Maybe Pad) -> m (Maybe Pad)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pad) -> m (Maybe Pad))
-> IO (Maybe Pad) -> m (Maybe Pad)
forall a b. (a -> b) -> a -> b
$ do
    Ptr GhostPad
gpad' <- a -> IO (Ptr GhostPad)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
gpad
    Ptr Pad
result <- Ptr GhostPad -> IO (Ptr Pad)
gst_ghost_pad_get_target Ptr GhostPad
gpad'
    Maybe Pad
maybeResult <- Ptr Pad -> (Ptr Pad -> IO Pad) -> IO (Maybe Pad)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pad
result ((Ptr Pad -> IO Pad) -> IO (Maybe Pad))
-> (Ptr Pad -> IO Pad) -> IO (Maybe Pad)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Pad
result' -> do
        Pad
result'' <- ((ManagedPtr Pad -> Pad) -> Ptr Pad -> IO Pad
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pad -> Pad
Gst.Pad.Pad) Ptr Pad
result'
        Pad -> IO Pad
forall (m :: * -> *) a. Monad m => a -> m a
return Pad
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
gpad
    Maybe Pad -> IO (Maybe Pad)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pad
maybeResult

#if defined(ENABLE_OVERLOADING)
data GhostPadGetTargetMethodInfo
instance (signature ~ (m (Maybe Gst.Pad.Pad)), MonadIO m, IsGhostPad a) => O.MethodInfo GhostPadGetTargetMethodInfo a signature where
    overloadedMethod = ghostPadGetTarget

#endif

-- method GhostPad::set_target
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "gpad"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "GhostPad" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GstGhostPad" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "newtarget"
--           , argType = TInterface Name { namespace = "Gst" , name = "Pad" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new pad target" , 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_ghost_pad_set_target" gst_ghost_pad_set_target :: 
    Ptr GhostPad ->                         -- gpad : TInterface (Name {namespace = "Gst", name = "GhostPad"})
    Ptr Gst.Pad.Pad ->                      -- newtarget : TInterface (Name {namespace = "Gst", name = "Pad"})
    IO CInt

-- | Set the new target of the ghostpad /@gpad@/. Any existing target
-- is unlinked and links to the new target are established. if /@newtarget@/ is
-- 'P.Nothing' the target will be cleared.
ghostPadSetTarget ::
    (B.CallStack.HasCallStack, MonadIO m, IsGhostPad a, Gst.Pad.IsPad b) =>
    a
    -- ^ /@gpad@/: the t'GI.Gst.Objects.GhostPad.GhostPad'
    -> Maybe (b)
    -- ^ /@newtarget@/: the new pad target
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the new target could be set. This function
    --     can return 'P.False' when the internal pads could not be linked.
ghostPadSetTarget :: a -> Maybe b -> m Bool
ghostPadSetTarget gpad :: a
gpad newtarget :: Maybe b
newtarget = IO Bool -> m Bool
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 GhostPad
gpad' <- a -> IO (Ptr GhostPad)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
gpad
    Ptr Pad
maybeNewtarget <- case Maybe b
newtarget of
        Nothing -> Ptr Pad -> IO (Ptr Pad)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Pad
forall a. Ptr a
nullPtr
        Just jNewtarget :: b
jNewtarget -> do
            Ptr Pad
jNewtarget' <- b -> IO (Ptr Pad)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jNewtarget
            Ptr Pad -> IO (Ptr Pad)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Pad
jNewtarget'
    CInt
result <- Ptr GhostPad -> Ptr Pad -> IO CInt
gst_ghost_pad_set_target Ptr GhostPad
gpad' Ptr Pad
maybeNewtarget
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
gpad
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
newtarget b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data GhostPadSetTargetMethodInfo
instance (signature ~ (Maybe (b) -> m Bool), MonadIO m, IsGhostPad a, Gst.Pad.IsPad b) => O.MethodInfo GhostPadSetTargetMethodInfo a signature where
    overloadedMethod = ghostPadSetTarget

#endif

-- method GhostPad::activate_mode_default
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "pad"
--           , argType = TInterface Name { namespace = "Gst" , name = "Pad" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GstPad to activate or deactivate."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parent"
--           , argType = TInterface Name { namespace = "Gst" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the parent of @pad or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mode"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "PadMode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the requested activation mode"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "active"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether the pad should be active or not."
--                 , 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_ghost_pad_activate_mode_default" gst_ghost_pad_activate_mode_default :: 
    Ptr Gst.Pad.Pad ->                      -- pad : TInterface (Name {namespace = "Gst", name = "Pad"})
    Ptr Gst.Object.Object ->                -- parent : TInterface (Name {namespace = "Gst", name = "Object"})
    CUInt ->                                -- mode : TInterface (Name {namespace = "Gst", name = "PadMode"})
    CInt ->                                 -- active : TBasicType TBoolean
    IO CInt

-- | Invoke the default activate mode function of a ghost pad.
ghostPadActivateModeDefault ::
    (B.CallStack.HasCallStack, MonadIO m, Gst.Pad.IsPad a, Gst.Object.IsObject b) =>
    a
    -- ^ /@pad@/: the t'GI.Gst.Objects.Pad.Pad' to activate or deactivate.
    -> Maybe (b)
    -- ^ /@parent@/: the parent of /@pad@/ or 'P.Nothing'
    -> Gst.Enums.PadMode
    -- ^ /@mode@/: the requested activation mode
    -> Bool
    -- ^ /@active@/: whether the pad should be active or not.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the operation was successful.
ghostPadActivateModeDefault :: a -> Maybe b -> PadMode -> Bool -> m Bool
ghostPadActivateModeDefault pad :: a
pad parent :: Maybe b
parent mode :: PadMode
mode active :: Bool
active = IO Bool -> m Bool
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 Pad
pad' <- a -> IO (Ptr Pad)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pad
    Ptr Object
maybeParent <- case Maybe b
parent of
        Nothing -> Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
forall a. Ptr a
nullPtr
        Just jParent :: b
jParent -> do
            Ptr Object
jParent' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jParent
            Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
jParent'
    let mode' :: CUInt
mode' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PadMode -> Int) -> PadMode -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PadMode -> Int
forall a. Enum a => a -> Int
fromEnum) PadMode
mode
    let active' :: CInt
active' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
active
    CInt
result <- Ptr Pad -> Ptr Object -> CUInt -> CInt -> IO CInt
gst_ghost_pad_activate_mode_default Ptr Pad
pad' Ptr Object
maybeParent CUInt
mode' CInt
active'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pad
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
parent b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method GhostPad::internal_activate_mode_default
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "pad"
--           , argType = TInterface Name { namespace = "Gst" , name = "Pad" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GstPad to activate or deactivate."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parent"
--           , argType = TInterface Name { namespace = "Gst" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the parent of @pad or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mode"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "PadMode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the requested activation mode"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "active"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether the pad should be active or not."
--                 , 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_ghost_pad_internal_activate_mode_default" gst_ghost_pad_internal_activate_mode_default :: 
    Ptr Gst.Pad.Pad ->                      -- pad : TInterface (Name {namespace = "Gst", name = "Pad"})
    Ptr Gst.Object.Object ->                -- parent : TInterface (Name {namespace = "Gst", name = "Object"})
    CUInt ->                                -- mode : TInterface (Name {namespace = "Gst", name = "PadMode"})
    CInt ->                                 -- active : TBasicType TBoolean
    IO CInt

-- | Invoke the default activate mode function of a proxy pad that is
-- owned by a ghost pad.
ghostPadInternalActivateModeDefault ::
    (B.CallStack.HasCallStack, MonadIO m, Gst.Pad.IsPad a, Gst.Object.IsObject b) =>
    a
    -- ^ /@pad@/: the t'GI.Gst.Objects.Pad.Pad' to activate or deactivate.
    -> Maybe (b)
    -- ^ /@parent@/: the parent of /@pad@/ or 'P.Nothing'
    -> Gst.Enums.PadMode
    -- ^ /@mode@/: the requested activation mode
    -> Bool
    -- ^ /@active@/: whether the pad should be active or not.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the operation was successful.
ghostPadInternalActivateModeDefault :: a -> Maybe b -> PadMode -> Bool -> m Bool
ghostPadInternalActivateModeDefault pad :: a
pad parent :: Maybe b
parent mode :: PadMode
mode active :: Bool
active = IO Bool -> m Bool
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 Pad
pad' <- a -> IO (Ptr Pad)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pad
    Ptr Object
maybeParent <- case Maybe b
parent of
        Nothing -> Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
forall a. Ptr a
nullPtr
        Just jParent :: b
jParent -> do
            Ptr Object
jParent' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jParent
            Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
jParent'
    let mode' :: CUInt
mode' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PadMode -> Int) -> PadMode -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PadMode -> Int
forall a. Enum a => a -> Int
fromEnum) PadMode
mode
    let active' :: CInt
active' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
active
    CInt
result <- Ptr Pad -> Ptr Object -> CUInt -> CInt -> IO CInt
gst_ghost_pad_internal_activate_mode_default Ptr Pad
pad' Ptr Object
maybeParent CUInt
mode' CInt
active'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pad
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
parent b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
#endif