{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Gst.Interfaces.URIHandler.URIHandler' is an interface that is implemented by Source and Sink
-- t'GI.Gst.Objects.Element.Element' to unify handling of URI.
-- 
-- An application can use the following functions to quickly get an element
-- that handles the given URI for reading or writing
-- ('GI.Gst.Objects.Element.elementMakeFromUri').
-- 
-- Source and Sink plugins should implement this interface when possible.

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

module GI.Gst.Interfaces.URIHandler
    ( 

-- * Exported types
    URIHandler(..)                          ,
    noURIHandler                            ,
    IsURIHandler                            ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveURIHandlerMethod                 ,
#endif


-- ** getProtocols #method:getProtocols#

#if defined(ENABLE_OVERLOADING)
    URIHandlerGetProtocolsMethodInfo        ,
#endif
    uRIHandlerGetProtocols                  ,


-- ** getUri #method:getUri#

#if defined(ENABLE_OVERLOADING)
    URIHandlerGetUriMethodInfo              ,
#endif
    uRIHandlerGetUri                        ,


-- ** getUriType #method:getUriType#

#if defined(ENABLE_OVERLOADING)
    URIHandlerGetUriTypeMethodInfo          ,
#endif
    uRIHandlerGetUriType                    ,


-- ** setUri #method:setUri#

#if defined(ENABLE_OVERLOADING)
    URIHandlerSetUriMethodInfo              ,
#endif
    uRIHandlerSetUri                        ,




    ) 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 {-# SOURCE #-} qualified GI.Gst.Enums as Gst.Enums

-- interface URIHandler 
-- | Memory-managed wrapper type.
newtype URIHandler = URIHandler (ManagedPtr URIHandler)
    deriving (URIHandler -> URIHandler -> Bool
(URIHandler -> URIHandler -> Bool)
-> (URIHandler -> URIHandler -> Bool) -> Eq URIHandler
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: URIHandler -> URIHandler -> Bool
$c/= :: URIHandler -> URIHandler -> Bool
== :: URIHandler -> URIHandler -> Bool
$c== :: URIHandler -> URIHandler -> Bool
Eq)
-- | A convenience alias for `Nothing` :: `Maybe` `URIHandler`.
noURIHandler :: Maybe URIHandler
noURIHandler :: Maybe URIHandler
noURIHandler = Maybe URIHandler
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList URIHandler = URIHandlerSignalList
type URIHandlerSignalList = ('[ ] :: [(Symbol, *)])

#endif

-- | Type class for types which implement `URIHandler`.
class (ManagedPtrNewtype o, O.IsDescendantOf URIHandler o) => IsURIHandler o
instance (ManagedPtrNewtype o, O.IsDescendantOf URIHandler o) => IsURIHandler o
-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance WrappedPtr URIHandler where
    wrappedPtrCalloc :: IO (Ptr URIHandler)
wrappedPtrCalloc = Ptr URIHandler -> IO (Ptr URIHandler)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr URIHandler
forall a. Ptr a
nullPtr
    wrappedPtrCopy :: URIHandler -> IO URIHandler
wrappedPtrCopy = URIHandler -> IO URIHandler
forall (m :: * -> *) a. Monad m => a -> m a
return
    wrappedPtrFree :: Maybe (GDestroyNotify URIHandler)
wrappedPtrFree = Maybe (GDestroyNotify URIHandler)
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
type family ResolveURIHandlerMethod (t :: Symbol) (o :: *) :: * where
    ResolveURIHandlerMethod "getProtocols" o = URIHandlerGetProtocolsMethodInfo
    ResolveURIHandlerMethod "getUri" o = URIHandlerGetUriMethodInfo
    ResolveURIHandlerMethod "getUriType" o = URIHandlerGetUriTypeMethodInfo
    ResolveURIHandlerMethod "setUri" o = URIHandlerSetUriMethodInfo
    ResolveURIHandlerMethod l o = O.MethodResolutionFailed l o

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

#endif

-- method URIHandler::get_protocols
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "handler"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "URIHandler" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GstURIHandler." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "gst_uri_handler_get_protocols" gst_uri_handler_get_protocols :: 
    Ptr URIHandler ->                       -- handler : TInterface (Name {namespace = "Gst", name = "URIHandler"})
    IO (Ptr CString)

-- | Gets the list of protocols supported by /@handler@/. This list may not be
-- modified.
uRIHandlerGetProtocols ::
    (B.CallStack.HasCallStack, MonadIO m, IsURIHandler a) =>
    a
    -- ^ /@handler@/: A t'GI.Gst.Interfaces.URIHandler.URIHandler'.
    -> m (Maybe [T.Text])
    -- ^ __Returns:__ the
    --     supported protocols.  Returns 'P.Nothing' if the /@handler@/ isn\'t
    --     implemented properly, or the /@handler@/ doesn\'t support any
    --     protocols.
uRIHandlerGetProtocols :: a -> m (Maybe [Text])
uRIHandlerGetProtocols handler :: a
handler = 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
$ do
    Ptr URIHandler
handler' <- a -> IO (Ptr URIHandler)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
handler
    Ptr CString
result <- Ptr URIHandler -> IO (Ptr CString)
gst_uri_handler_get_protocols Ptr URIHandler
handler'
    Maybe [Text]
maybeResult <- Ptr CString -> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CString
result ((Ptr CString -> IO [Text]) -> IO (Maybe [Text]))
-> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr CString
result' -> do
        [Text]
result'' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result'
        [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
handler
    Maybe [Text] -> IO (Maybe [Text])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Text]
maybeResult

#if defined(ENABLE_OVERLOADING)
data URIHandlerGetProtocolsMethodInfo
instance (signature ~ (m (Maybe [T.Text])), MonadIO m, IsURIHandler a) => O.MethodInfo URIHandlerGetProtocolsMethodInfo a signature where
    overloadedMethod = uRIHandlerGetProtocols

#endif

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

foreign import ccall "gst_uri_handler_get_uri" gst_uri_handler_get_uri :: 
    Ptr URIHandler ->                       -- handler : TInterface (Name {namespace = "Gst", name = "URIHandler"})
    IO CString

-- | Gets the currently handled URI.
uRIHandlerGetUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsURIHandler a) =>
    a
    -- ^ /@handler@/: A t'GI.Gst.Interfaces.URIHandler.URIHandler'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the URI currently handled by
    --   the /@handler@/.  Returns 'P.Nothing' if there are no URI currently
    --   handled. The returned string must be freed with 'GI.GLib.Functions.free' when no
    --   longer needed.
uRIHandlerGetUri :: a -> m (Maybe Text)
uRIHandlerGetUri handler :: a
handler = 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
$ do
    Ptr URIHandler
handler' <- a -> IO (Ptr URIHandler)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
handler
    CString
result <- Ptr URIHandler -> IO CString
gst_uri_handler_get_uri Ptr URIHandler
handler'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \result' :: CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
handler
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data URIHandlerGetUriMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsURIHandler a) => O.MethodInfo URIHandlerGetUriMethodInfo a signature where
    overloadedMethod = uRIHandlerGetUri

#endif

-- method URIHandler::get_uri_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "handler"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "URIHandler" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GstURIHandler." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "URIType" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_uri_handler_get_uri_type" gst_uri_handler_get_uri_type :: 
    Ptr URIHandler ->                       -- handler : TInterface (Name {namespace = "Gst", name = "URIHandler"})
    IO CUInt

-- | Gets the type of the given URI handler
uRIHandlerGetUriType ::
    (B.CallStack.HasCallStack, MonadIO m, IsURIHandler a) =>
    a
    -- ^ /@handler@/: A t'GI.Gst.Interfaces.URIHandler.URIHandler'.
    -> m Gst.Enums.URIType
    -- ^ __Returns:__ the t'GI.Gst.Enums.URIType' of the URI handler.
    -- Returns @/GST_URI_UNKNOWN/@ if the /@handler@/ isn\'t implemented correctly.
uRIHandlerGetUriType :: a -> m URIType
uRIHandlerGetUriType handler :: a
handler = IO URIType -> m URIType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO URIType -> m URIType) -> IO URIType -> m URIType
forall a b. (a -> b) -> a -> b
$ do
    Ptr URIHandler
handler' <- a -> IO (Ptr URIHandler)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
handler
    CUInt
result <- Ptr URIHandler -> IO CUInt
gst_uri_handler_get_uri_type Ptr URIHandler
handler'
    let result' :: URIType
result' = (Int -> URIType
forall a. Enum a => Int -> a
toEnum (Int -> URIType) -> (CUInt -> Int) -> CUInt -> URIType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
handler
    URIType -> IO URIType
forall (m :: * -> *) a. Monad m => a -> m a
return URIType
result'

#if defined(ENABLE_OVERLOADING)
data URIHandlerGetUriTypeMethodInfo
instance (signature ~ (m Gst.Enums.URIType), MonadIO m, IsURIHandler a) => O.MethodInfo URIHandlerGetUriTypeMethodInfo a signature where
    overloadedMethod = uRIHandlerGetUriType

#endif

-- method URIHandler::set_uri
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "handler"
--           , argType =
--               TInterface Name { namespace = "Gst" , name = "URIHandler" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GstURIHandler" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "URI to set" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "gst_uri_handler_set_uri" gst_uri_handler_set_uri :: 
    Ptr URIHandler ->                       -- handler : TInterface (Name {namespace = "Gst", name = "URIHandler"})
    CString ->                              -- uri : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Tries to set the URI of the given handler.
uRIHandlerSetUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsURIHandler a) =>
    a
    -- ^ /@handler@/: A t'GI.Gst.Interfaces.URIHandler.URIHandler'
    -> T.Text
    -- ^ /@uri@/: URI to set
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
uRIHandlerSetUri :: a -> Text -> m ()
uRIHandlerSetUri handler :: a
handler uri :: Text
uri = 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 URIHandler
handler' <- a -> IO (Ptr URIHandler)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
handler
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr URIHandler -> CString -> Ptr (Ptr GError) -> IO CInt
gst_uri_handler_set_uri Ptr URIHandler
handler' CString
uri'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
handler
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
     )

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

#endif