{-# 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.WebKit2.Objects.Plugin
    ( 

-- * Exported types
    Plugin(..)                              ,
    IsPlugin                                ,
    toPlugin                                ,


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

#if defined(ENABLE_OVERLOADING)
    ResolvePluginMethod                     ,
#endif


-- ** getDescription #method:getDescription#

#if defined(ENABLE_OVERLOADING)
    PluginGetDescriptionMethodInfo          ,
#endif
    pluginGetDescription                    ,


-- ** getMimeInfoList #method:getMimeInfoList#

#if defined(ENABLE_OVERLOADING)
    PluginGetMimeInfoListMethodInfo         ,
#endif
    pluginGetMimeInfoList                   ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    PluginGetNameMethodInfo                 ,
#endif
    pluginGetName                           ,


-- ** getPath #method:getPath#

#if defined(ENABLE_OVERLOADING)
    PluginGetPathMethodInfo                 ,
#endif
    pluginGetPath                           ,




    ) 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.WebKit2.Structs.MimeInfo as WebKit2.MimeInfo

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

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

foreign import ccall "webkit_plugin_get_type"
    c_webkit_plugin_get_type :: IO B.Types.GType

instance B.Types.TypedObject Plugin where
    glibType :: IO GType
glibType = IO GType
c_webkit_plugin_get_type

instance B.Types.GObject Plugin

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolvePluginMethod (t :: Symbol) (o :: *) :: * where
    ResolvePluginMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePluginMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePluginMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePluginMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePluginMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePluginMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePluginMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePluginMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePluginMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePluginMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePluginMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePluginMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePluginMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePluginMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePluginMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePluginMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePluginMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePluginMethod "getDescription" o = PluginGetDescriptionMethodInfo
    ResolvePluginMethod "getMimeInfoList" o = PluginGetMimeInfoListMethodInfo
    ResolvePluginMethod "getName" o = PluginGetNameMethodInfo
    ResolvePluginMethod "getPath" o = PluginGetPathMethodInfo
    ResolvePluginMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePluginMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePluginMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePluginMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePluginMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePluginMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolvePluginMethod t Plugin, O.MethodInfo info Plugin p) => OL.IsLabel t (Plugin -> 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 Plugin
type instance O.AttributeList Plugin = PluginAttributeList
type PluginAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method Plugin::get_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "plugin"
--           , argType =
--               TInterface Name { namespace = "WebKit2" , name = "Plugin" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitPlugin" , 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_plugin_get_description" webkit_plugin_get_description :: 
    Ptr Plugin ->                           -- plugin : TInterface (Name {namespace = "WebKit2", name = "Plugin"})
    IO CString

-- | /No description available in the introspection data./
pluginGetDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsPlugin a) =>
    a
    -- ^ /@plugin@/: a t'GI.WebKit2.Objects.Plugin.Plugin'
    -> m T.Text
    -- ^ __Returns:__ the description of the plugin.
pluginGetDescription :: a -> m Text
pluginGetDescription a
plugin = 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 Plugin
plugin' <- a -> IO (Ptr Plugin)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
plugin
    CString
result <- Ptr Plugin -> IO CString
webkit_plugin_get_description Ptr Plugin
plugin'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pluginGetDescription" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
plugin
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data PluginGetDescriptionMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPlugin a) => O.MethodInfo PluginGetDescriptionMethodInfo a signature where
    overloadedMethod = pluginGetDescription

#endif

-- method Plugin::get_mime_info_list
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "plugin"
--           , argType =
--               TInterface Name { namespace = "WebKit2" , name = "Plugin" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitPlugin" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList
--                  (TInterface Name { namespace = "WebKit2" , name = "MimeInfo" }))
-- throws : False
-- Skip return : False

foreign import ccall "webkit_plugin_get_mime_info_list" webkit_plugin_get_mime_info_list :: 
    Ptr Plugin ->                           -- plugin : TInterface (Name {namespace = "WebKit2", name = "Plugin"})
    IO (Ptr (GList (Ptr WebKit2.MimeInfo.MimeInfo)))

-- | Get information about MIME types handled by the plugin,
-- as a list of t'GI.WebKit2.Structs.MimeInfo.MimeInfo'.
pluginGetMimeInfoList ::
    (B.CallStack.HasCallStack, MonadIO m, IsPlugin a) =>
    a
    -- ^ /@plugin@/: a t'GI.WebKit2.Objects.Plugin.Plugin'
    -> m [WebKit2.MimeInfo.MimeInfo]
    -- ^ __Returns:__ a t'GI.GLib.Structs.List.List' of t'GI.WebKit2.Structs.MimeInfo.MimeInfo'.
pluginGetMimeInfoList :: a -> m [MimeInfo]
pluginGetMimeInfoList a
plugin = IO [MimeInfo] -> m [MimeInfo]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [MimeInfo] -> m [MimeInfo]) -> IO [MimeInfo] -> m [MimeInfo]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Plugin
plugin' <- a -> IO (Ptr Plugin)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
plugin
    Ptr (GList (Ptr MimeInfo))
result <- Ptr Plugin -> IO (Ptr (GList (Ptr MimeInfo)))
webkit_plugin_get_mime_info_list Ptr Plugin
plugin'
    [Ptr MimeInfo]
result' <- Ptr (GList (Ptr MimeInfo)) -> IO [Ptr MimeInfo]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr MimeInfo))
result
    [MimeInfo]
result'' <- (Ptr MimeInfo -> IO MimeInfo) -> [Ptr MimeInfo] -> IO [MimeInfo]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr MimeInfo -> MimeInfo) -> Ptr MimeInfo -> IO MimeInfo
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr MimeInfo -> MimeInfo
WebKit2.MimeInfo.MimeInfo) [Ptr MimeInfo]
result'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
plugin
    [MimeInfo] -> IO [MimeInfo]
forall (m :: * -> *) a. Monad m => a -> m a
return [MimeInfo]
result''

#if defined(ENABLE_OVERLOADING)
data PluginGetMimeInfoListMethodInfo
instance (signature ~ (m [WebKit2.MimeInfo.MimeInfo]), MonadIO m, IsPlugin a) => O.MethodInfo PluginGetMimeInfoListMethodInfo a signature where
    overloadedMethod = pluginGetMimeInfoList

#endif

-- method Plugin::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "plugin"
--           , argType =
--               TInterface Name { namespace = "WebKit2" , name = "Plugin" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitPlugin" , 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_plugin_get_name" webkit_plugin_get_name :: 
    Ptr Plugin ->                           -- plugin : TInterface (Name {namespace = "WebKit2", name = "Plugin"})
    IO CString

-- | /No description available in the introspection data./
pluginGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsPlugin a) =>
    a
    -- ^ /@plugin@/: a t'GI.WebKit2.Objects.Plugin.Plugin'
    -> m T.Text
    -- ^ __Returns:__ the name of the plugin.
pluginGetName :: a -> m Text
pluginGetName a
plugin = 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 Plugin
plugin' <- a -> IO (Ptr Plugin)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
plugin
    CString
result <- Ptr Plugin -> IO CString
webkit_plugin_get_name Ptr Plugin
plugin'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pluginGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
plugin
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data PluginGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPlugin a) => O.MethodInfo PluginGetNameMethodInfo a signature where
    overloadedMethod = pluginGetName

#endif

-- method Plugin::get_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "plugin"
--           , argType =
--               TInterface Name { namespace = "WebKit2" , name = "Plugin" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitPlugin" , 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_plugin_get_path" webkit_plugin_get_path :: 
    Ptr Plugin ->                           -- plugin : TInterface (Name {namespace = "WebKit2", name = "Plugin"})
    IO CString

-- | /No description available in the introspection data./
pluginGetPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsPlugin a) =>
    a
    -- ^ /@plugin@/: a t'GI.WebKit2.Objects.Plugin.Plugin'
    -> m T.Text
    -- ^ __Returns:__ the absolute path where the plugin is installed.
pluginGetPath :: a -> m Text
pluginGetPath a
plugin = 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 Plugin
plugin' <- a -> IO (Ptr Plugin)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
plugin
    CString
result <- Ptr Plugin -> IO CString
webkit_plugin_get_path Ptr Plugin
plugin'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"pluginGetPath" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
plugin
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data PluginGetPathMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPlugin a) => O.MethodInfo PluginGetPathMethodInfo a signature where
    overloadedMethod = pluginGetPath

#endif