{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Represents a scope for loading IO modules. A scope can be used for blocking
-- duplicate modules, or blocking a module you don\'t want to load.
-- 
-- The scope can be used with @/g_io_modules_load_all_in_directory_with_scope()/@
-- or 'GI.Gio.Functions.ioModulesScanAllInDirectoryWithScope'.
-- 
-- /Since: 2.30/

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

module GI.Gio.Structs.IOModuleScope
    ( 

-- * Exported types
    IOModuleScope(..)                       ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [block]("GI.Gio.Structs.IOModuleScope#g:method:block"), [free]("GI.Gio.Structs.IOModuleScope#g:method:free").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveIOModuleScopeMethod              ,
#endif

-- ** block #method:block#

#if defined(ENABLE_OVERLOADING)
    IOModuleScopeBlockMethodInfo            ,
#endif
    iOModuleScopeBlock                      ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    IOModuleScopeFreeMethodInfo             ,
#endif
    iOModuleScopeFree                       ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R


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

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

-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance BoxedPtr IOModuleScope where
    boxedPtrCopy :: IOModuleScope -> IO IOModuleScope
boxedPtrCopy = IOModuleScope -> IO IOModuleScope
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: IOModuleScope -> IO ()
boxedPtrFree = \IOModuleScope
_x -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList IOModuleScope
type instance O.AttributeList IOModuleScope = IOModuleScopeAttributeList
type IOModuleScopeAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method IOModuleScope::block
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "scope"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "IOModuleScope" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a module loading scope"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "basename"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the basename to block"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_io_module_scope_block" g_io_module_scope_block :: 
    Ptr IOModuleScope ->                    -- scope : TInterface (Name {namespace = "Gio", name = "IOModuleScope"})
    CString ->                              -- basename : TBasicType TUTF8
    IO ()

-- | Block modules with the given /@basename@/ from being loaded when
-- this scope is used with 'GI.Gio.Functions.ioModulesScanAllInDirectoryWithScope'
-- or @/g_io_modules_load_all_in_directory_with_scope()/@.
-- 
-- /Since: 2.30/
iOModuleScopeBlock ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    IOModuleScope
    -- ^ /@scope@/: a module loading scope
    -> T.Text
    -- ^ /@basename@/: the basename to block
    -> m ()
iOModuleScopeBlock :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
IOModuleScope -> Text -> m ()
iOModuleScopeBlock IOModuleScope
scope Text
basename = 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 IOModuleScope
scope' <- IOModuleScope -> IO (Ptr IOModuleScope)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IOModuleScope
scope
    CString
basename' <- Text -> IO CString
textToCString Text
basename
    Ptr IOModuleScope -> CString -> IO ()
g_io_module_scope_block Ptr IOModuleScope
scope' CString
basename'
    IOModuleScope -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IOModuleScope
scope
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
basename'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data IOModuleScopeBlockMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.OverloadedMethod IOModuleScopeBlockMethodInfo IOModuleScope signature where
    overloadedMethod = iOModuleScopeBlock

instance O.OverloadedMethodInfo IOModuleScopeBlockMethodInfo IOModuleScope where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Structs.IOModuleScope.iOModuleScopeBlock",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Structs-IOModuleScope.html#v:iOModuleScopeBlock"
        })


#endif

-- method IOModuleScope::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "scope"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "IOModuleScope" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a module loading scope"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_io_module_scope_free" g_io_module_scope_free :: 
    Ptr IOModuleScope ->                    -- scope : TInterface (Name {namespace = "Gio", name = "IOModuleScope"})
    IO ()

-- | Free a module scope.
-- 
-- /Since: 2.30/
iOModuleScopeFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    IOModuleScope
    -- ^ /@scope@/: a module loading scope
    -> m ()
iOModuleScopeFree :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
IOModuleScope -> m ()
iOModuleScopeFree IOModuleScope
scope = 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 IOModuleScope
scope' <- IOModuleScope -> IO (Ptr IOModuleScope)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IOModuleScope
scope
    Ptr IOModuleScope -> IO ()
g_io_module_scope_free Ptr IOModuleScope
scope'
    IOModuleScope -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IOModuleScope
scope
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data IOModuleScopeFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod IOModuleScopeFreeMethodInfo IOModuleScope signature where
    overloadedMethod = iOModuleScopeFree

instance O.OverloadedMethodInfo IOModuleScopeFreeMethodInfo IOModuleScope where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Structs.IOModuleScope.iOModuleScopeFree",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Structs-IOModuleScope.html#v:iOModuleScopeFree"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveIOModuleScopeMethod (t :: Symbol) (o :: *) :: * where
    ResolveIOModuleScopeMethod "block" o = IOModuleScopeBlockMethodInfo
    ResolveIOModuleScopeMethod "free" o = IOModuleScopeFreeMethodInfo
    ResolveIOModuleScopeMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveIOModuleScopeMethod t IOModuleScope, O.OverloadedMethod info IOModuleScope p, R.HasField t IOModuleScope p) => R.HasField t IOModuleScope p where
    getField = O.overloadedMethod @info

#endif

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

#endif