{-# LANGUAGE TypeApplications #-}


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

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

module GI.WebKit2WebExtension.Objects.DOMMediaList
    ( 

-- * Exported types
    DOMMediaList(..)                        ,
    IsDOMMediaList                          ,
    toDOMMediaList                          ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveDOMMediaListMethod               ,
#endif


-- ** appendMedium #method:appendMedium#

#if defined(ENABLE_OVERLOADING)
    DOMMediaListAppendMediumMethodInfo      ,
#endif
    dOMMediaListAppendMedium                ,


-- ** deleteMedium #method:deleteMedium#

#if defined(ENABLE_OVERLOADING)
    DOMMediaListDeleteMediumMethodInfo      ,
#endif
    dOMMediaListDeleteMedium                ,


-- ** getLength #method:getLength#

#if defined(ENABLE_OVERLOADING)
    DOMMediaListGetLengthMethodInfo         ,
#endif
    dOMMediaListGetLength                   ,


-- ** getMediaText #method:getMediaText#

#if defined(ENABLE_OVERLOADING)
    DOMMediaListGetMediaTextMethodInfo      ,
#endif
    dOMMediaListGetMediaText                ,


-- ** item #method:item#

#if defined(ENABLE_OVERLOADING)
    DOMMediaListItemMethodInfo              ,
#endif
    dOMMediaListItem                        ,


-- ** setMediaText #method:setMediaText#

#if defined(ENABLE_OVERLOADING)
    DOMMediaListSetMediaTextMethodInfo      ,
#endif
    dOMMediaListSetMediaText                ,




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

#if defined(ENABLE_OVERLOADING)
    DOMMediaListLengthPropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    dOMMediaListLength                      ,
#endif
    getDOMMediaListLength                   ,


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

#if defined(ENABLE_OVERLOADING)
    DOMMediaListMediaTextPropertyInfo       ,
#endif
    clearDOMMediaListMediaText              ,
    constructDOMMediaListMediaText          ,
#if defined(ENABLE_OVERLOADING)
    dOMMediaListMediaText                   ,
#endif
    getDOMMediaListMediaText                ,
    setDOMMediaListMediaText                ,




    ) 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.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 Control.Monad.IO.Class as MIO
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.WebKit2WebExtension.Objects.DOMObject as WebKit2WebExtension.DOMObject

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

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

foreign import ccall "webkit_dom_media_list_get_type"
    c_webkit_dom_media_list_get_type :: IO B.Types.GType

instance B.Types.TypedObject DOMMediaList where
    glibType :: IO GType
glibType = IO GType
c_webkit_dom_media_list_get_type

instance B.Types.GObject DOMMediaList

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

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

instance O.HasParentTypes DOMMediaList
type instance O.ParentTypes DOMMediaList = '[WebKit2WebExtension.DOMObject.DOMObject, GObject.Object.Object]

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

#if defined(ENABLE_OVERLOADING)
type family ResolveDOMMediaListMethod (t :: Symbol) (o :: *) :: * where
    ResolveDOMMediaListMethod "appendMedium" o = DOMMediaListAppendMediumMethodInfo
    ResolveDOMMediaListMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDOMMediaListMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDOMMediaListMethod "deleteMedium" o = DOMMediaListDeleteMediumMethodInfo
    ResolveDOMMediaListMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDOMMediaListMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDOMMediaListMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDOMMediaListMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDOMMediaListMethod "item" o = DOMMediaListItemMethodInfo
    ResolveDOMMediaListMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDOMMediaListMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDOMMediaListMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDOMMediaListMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDOMMediaListMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDOMMediaListMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDOMMediaListMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDOMMediaListMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDOMMediaListMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDOMMediaListMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDOMMediaListMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDOMMediaListMethod "getLength" o = DOMMediaListGetLengthMethodInfo
    ResolveDOMMediaListMethod "getMediaText" o = DOMMediaListGetMediaTextMethodInfo
    ResolveDOMMediaListMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDOMMediaListMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDOMMediaListMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDOMMediaListMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDOMMediaListMethod "setMediaText" o = DOMMediaListSetMediaTextMethodInfo
    ResolveDOMMediaListMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDOMMediaListMethod l o = O.MethodResolutionFailed l o

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

#endif

-- VVV Prop "length"
   -- Type: TBasicType TULong
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@length@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMediaList #length
-- @
getDOMMediaListLength :: (MonadIO m, IsDOMMediaList o) => o -> m CULong
getDOMMediaListLength :: o -> m CULong
getDOMMediaListLength o
obj = IO CULong -> m CULong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CULong -> m CULong) -> IO CULong -> m CULong
forall a b. (a -> b) -> a -> b
$ o -> String -> IO CULong
forall a. GObject a => a -> String -> IO CULong
B.Properties.getObjectPropertyULong o
obj String
"length"

#if defined(ENABLE_OVERLOADING)
data DOMMediaListLengthPropertyInfo
instance AttrInfo DOMMediaListLengthPropertyInfo where
    type AttrAllowedOps DOMMediaListLengthPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DOMMediaListLengthPropertyInfo = IsDOMMediaList
    type AttrSetTypeConstraint DOMMediaListLengthPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DOMMediaListLengthPropertyInfo = (~) ()
    type AttrTransferType DOMMediaListLengthPropertyInfo = ()
    type AttrGetType DOMMediaListLengthPropertyInfo = CULong
    type AttrLabel DOMMediaListLengthPropertyInfo = "length"
    type AttrOrigin DOMMediaListLengthPropertyInfo = DOMMediaList
    attrGet = getDOMMediaListLength
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "media-text"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@media-text@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dOMMediaList #mediaText
-- @
getDOMMediaListMediaText :: (MonadIO m, IsDOMMediaList o) => o -> m (Maybe T.Text)
getDOMMediaListMediaText :: o -> m (Maybe Text)
getDOMMediaListMediaText o
obj = IO (Maybe Text) -> m (Maybe Text)
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
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"media-text"

-- | Set the value of the “@media-text@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dOMMediaList [ #mediaText 'Data.GI.Base.Attributes.:=' value ]
-- @
setDOMMediaListMediaText :: (MonadIO m, IsDOMMediaList o) => o -> T.Text -> m ()
setDOMMediaListMediaText :: o -> Text -> m ()
setDOMMediaListMediaText o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"media-text" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@media-text@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDOMMediaListMediaText :: (IsDOMMediaList o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDOMMediaListMediaText :: Text -> m (GValueConstruct o)
constructDOMMediaListMediaText Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"media-text" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@media-text@” 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' #mediaText
-- @
clearDOMMediaListMediaText :: (MonadIO m, IsDOMMediaList o) => o -> m ()
clearDOMMediaListMediaText :: o -> m ()
clearDOMMediaListMediaText o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"media-text" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data DOMMediaListMediaTextPropertyInfo
instance AttrInfo DOMMediaListMediaTextPropertyInfo where
    type AttrAllowedOps DOMMediaListMediaTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DOMMediaListMediaTextPropertyInfo = IsDOMMediaList
    type AttrSetTypeConstraint DOMMediaListMediaTextPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DOMMediaListMediaTextPropertyInfo = (~) T.Text
    type AttrTransferType DOMMediaListMediaTextPropertyInfo = T.Text
    type AttrGetType DOMMediaListMediaTextPropertyInfo = (Maybe T.Text)
    type AttrLabel DOMMediaListMediaTextPropertyInfo = "media-text"
    type AttrOrigin DOMMediaListMediaTextPropertyInfo = DOMMediaList
    attrGet = getDOMMediaListMediaText
    attrSet = setDOMMediaListMediaText
    attrTransfer _ v = do
        return v
    attrConstruct = constructDOMMediaListMediaText
    attrClear = clearDOMMediaListMediaText
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DOMMediaList
type instance O.AttributeList DOMMediaList = DOMMediaListAttributeList
type DOMMediaListAttributeList = ('[ '("coreObject", WebKit2WebExtension.DOMObject.DOMObjectCoreObjectPropertyInfo), '("length", DOMMediaListLengthPropertyInfo), '("mediaText", DOMMediaListMediaTextPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
dOMMediaListLength :: AttrLabelProxy "length"
dOMMediaListLength = AttrLabelProxy

dOMMediaListMediaText :: AttrLabelProxy "mediaText"
dOMMediaListMediaText = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DOMMediaList = DOMMediaListSignalList
type DOMMediaListSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method DOMMediaList::append_medium
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMediaList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMediaList"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "newMedium"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_media_list_append_medium" webkit_dom_media_list_append_medium :: 
    Ptr DOMMediaList ->                     -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMediaList"})
    CString ->                              -- newMedium : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO ()

{-# DEPRECATED dOMMediaListAppendMedium ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMediaListAppendMedium ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMediaList a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMediaList.DOMMediaList'
    -> T.Text
    -- ^ /@newMedium@/: A @/gchar/@
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dOMMediaListAppendMedium :: a -> Text -> m ()
dOMMediaListAppendMedium a
self Text
newMedium = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMediaList
self' <- a -> IO (Ptr DOMMediaList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
newMedium' <- Text -> IO CString
textToCString Text
newMedium
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO ()) -> IO ())
-> (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DOMMediaList -> CString -> Ptr (Ptr GError) -> IO ()
webkit_dom_media_list_append_medium Ptr DOMMediaList
self' CString
newMedium'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
newMedium'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
newMedium'
     )

#if defined(ENABLE_OVERLOADING)
data DOMMediaListAppendMediumMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDOMMediaList a) => O.MethodInfo DOMMediaListAppendMediumMethodInfo a signature where
    overloadedMethod = dOMMediaListAppendMedium

#endif

-- method DOMMediaList::delete_medium
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMediaList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMediaList"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "oldMedium"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_media_list_delete_medium" webkit_dom_media_list_delete_medium :: 
    Ptr DOMMediaList ->                     -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMediaList"})
    CString ->                              -- oldMedium : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO ()

{-# DEPRECATED dOMMediaListDeleteMedium ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMediaListDeleteMedium ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMediaList a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMediaList.DOMMediaList'
    -> T.Text
    -- ^ /@oldMedium@/: A @/gchar/@
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dOMMediaListDeleteMedium :: a -> Text -> m ()
dOMMediaListDeleteMedium a
self Text
oldMedium = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMediaList
self' <- a -> IO (Ptr DOMMediaList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
oldMedium' <- Text -> IO CString
textToCString Text
oldMedium
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO ()) -> IO ())
-> (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DOMMediaList -> CString -> Ptr (Ptr GError) -> IO ()
webkit_dom_media_list_delete_medium Ptr DOMMediaList
self' CString
oldMedium'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
oldMedium'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
oldMedium'
     )

#if defined(ENABLE_OVERLOADING)
data DOMMediaListDeleteMediumMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDOMMediaList a) => O.MethodInfo DOMMediaListDeleteMediumMethodInfo a signature where
    overloadedMethod = dOMMediaListDeleteMedium

#endif

-- method DOMMediaList::get_length
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMediaList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMediaList"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TULong)
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_media_list_get_length" webkit_dom_media_list_get_length :: 
    Ptr DOMMediaList ->                     -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMediaList"})
    IO CULong

{-# DEPRECATED dOMMediaListGetLength ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMediaListGetLength ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMediaList a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMediaList.DOMMediaList'
    -> m CULong
    -- ^ __Returns:__ A @/gulong/@
dOMMediaListGetLength :: a -> m CULong
dOMMediaListGetLength a
self = IO CULong -> m CULong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CULong -> m CULong) -> IO CULong -> m CULong
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMediaList
self' <- a -> IO (Ptr DOMMediaList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CULong
result <- Ptr DOMMediaList -> IO CULong
webkit_dom_media_list_get_length Ptr DOMMediaList
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CULong -> IO CULong
forall (m :: * -> *) a. Monad m => a -> m a
return CULong
result

#if defined(ENABLE_OVERLOADING)
data DOMMediaListGetLengthMethodInfo
instance (signature ~ (m CULong), MonadIO m, IsDOMMediaList a) => O.MethodInfo DOMMediaListGetLengthMethodInfo a signature where
    overloadedMethod = dOMMediaListGetLength

#endif

-- method DOMMediaList::get_media_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMediaList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMediaList"
--                 , 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 "webkit_dom_media_list_get_media_text" webkit_dom_media_list_get_media_text :: 
    Ptr DOMMediaList ->                     -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMediaList"})
    IO CString

{-# DEPRECATED dOMMediaListGetMediaText ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMediaListGetMediaText ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMediaList a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMediaList.DOMMediaList'
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMMediaListGetMediaText :: a -> m Text
dOMMediaListGetMediaText a
self = IO Text -> m Text
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 DOMMediaList
self' <- a -> IO (Ptr DOMMediaList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMMediaList -> IO CString
webkit_dom_media_list_get_media_text Ptr DOMMediaList
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMMediaListGetMediaText" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DOMMediaListGetMediaTextMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDOMMediaList a) => O.MethodInfo DOMMediaListGetMediaTextMethodInfo a signature where
    overloadedMethod = dOMMediaListGetMediaText

#endif

-- method DOMMediaList::item
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMediaList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMediaList"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index"
--           , argType = TBasicType TULong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gulong" , 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 "webkit_dom_media_list_item" webkit_dom_media_list_item :: 
    Ptr DOMMediaList ->                     -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMediaList"})
    CULong ->                               -- index : TBasicType TULong
    IO CString

{-# DEPRECATED dOMMediaListItem ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMediaListItem ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMediaList a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMediaList.DOMMediaList'
    -> CULong
    -- ^ /@index@/: A @/gulong/@
    -> m T.Text
    -- ^ __Returns:__ A @/gchar/@
dOMMediaListItem :: a -> CULong -> m Text
dOMMediaListItem a
self CULong
index = IO Text -> m Text
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 DOMMediaList
self' <- a -> IO (Ptr DOMMediaList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr DOMMediaList -> CULong -> IO CString
webkit_dom_media_list_item Ptr DOMMediaList
self' CULong
index
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dOMMediaListItem" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DOMMediaListItemMethodInfo
instance (signature ~ (CULong -> m T.Text), MonadIO m, IsDOMMediaList a) => O.MethodInfo DOMMediaListItemMethodInfo a signature where
    overloadedMethod = dOMMediaListItem

#endif

-- method DOMMediaList::set_media_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "WebKit2WebExtension" , name = "DOMMediaList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #WebKitDOMMediaList"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #gchar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : True
-- Skip return : False

foreign import ccall "webkit_dom_media_list_set_media_text" webkit_dom_media_list_set_media_text :: 
    Ptr DOMMediaList ->                     -- self : TInterface (Name {namespace = "WebKit2WebExtension", name = "DOMMediaList"})
    CString ->                              -- value : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO ()

{-# DEPRECATED dOMMediaListSetMediaText ["(Since version 2.22)","Use JavaScriptCore API instead"] #-}
-- | /No description available in the introspection data./
dOMMediaListSetMediaText ::
    (B.CallStack.HasCallStack, MonadIO m, IsDOMMediaList a) =>
    a
    -- ^ /@self@/: A t'GI.WebKit2WebExtension.Objects.DOMMediaList.DOMMediaList'
    -> T.Text
    -- ^ /@value@/: A @/gchar/@
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dOMMediaListSetMediaText :: a -> Text -> m ()
dOMMediaListSetMediaText a
self Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DOMMediaList
self' <- a -> IO (Ptr DOMMediaList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
value' <- Text -> IO CString
textToCString Text
value
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO ()) -> IO ())
-> (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DOMMediaList -> CString -> Ptr (Ptr GError) -> IO ()
webkit_dom_media_list_set_media_text Ptr DOMMediaList
self' CString
value'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
     )

#if defined(ENABLE_OVERLOADING)
data DOMMediaListSetMediaTextMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDOMMediaList a) => O.MethodInfo DOMMediaListSetMediaTextMethodInfo a signature where
    overloadedMethod = dOMMediaListSetMediaText

#endif