{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkBuilderScope@ is an interface to provide language binding support
-- to @GtkBuilder@.
-- 
-- The goal of @GtkBuilderScope@ is to look up programming-language-specific
-- values for strings that are given in a @GtkBuilder@ UI file.
-- 
-- The primary intended audience is bindings that want to provide deeper
-- integration of @GtkBuilder@ into the language.
-- 
-- A @GtkBuilderScope@ instance may be used with multiple @GtkBuilder@ objects,
-- even at once.
-- 
-- By default, GTK will use its own implementation of @GtkBuilderScope@
-- for the C language which can be created via 'GI.Gtk.Objects.BuilderCScope.builderCScopeNew'.
-- 
-- If you implement @GtkBuilderScope@ for a language binding, you
-- may want to (partially) derive from or fall back to a t'GI.Gtk.Objects.BuilderCScope.BuilderCScope',
-- as that class implements support for automatic lookups from C symbols.

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

module GI.Gtk.Interfaces.BuilderScope
    ( 

-- * Exported types
    BuilderScope(..)                        ,
    IsBuilderScope                          ,
    toBuilderScope                          ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveBuilderScopeMethod               ,
#endif



    ) 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.GHashTable as B.GHT
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.Kind as DK
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

import qualified GI.GObject.Objects.Object as GObject.Object

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

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

foreign import ccall "gtk_builder_scope_get_type"
    c_gtk_builder_scope_get_type :: IO B.Types.GType

instance B.Types.TypedObject BuilderScope where
    glibType :: IO GType
glibType = IO GType
c_gtk_builder_scope_get_type

instance B.Types.GObject BuilderScope

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

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

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

-- | Convert 'BuilderScope' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe BuilderScope) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_builder_scope_get_type
    gvalueSet_ :: Ptr GValue -> Maybe BuilderScope -> IO ()
gvalueSet_ Ptr GValue
gv Maybe BuilderScope
P.Nothing = Ptr GValue -> Ptr BuilderScope -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr BuilderScope
forall a. Ptr a
FP.nullPtr :: FP.Ptr BuilderScope)
    gvalueSet_ Ptr GValue
gv (P.Just BuilderScope
obj) = BuilderScope -> (Ptr BuilderScope -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr BuilderScope
obj (Ptr GValue -> Ptr BuilderScope -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe BuilderScope)
gvalueGet_ Ptr GValue
gv = do
        Ptr BuilderScope
ptr <- Ptr GValue -> IO (Ptr BuilderScope)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr BuilderScope)
        if Ptr BuilderScope
ptr Ptr BuilderScope -> Ptr BuilderScope -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr BuilderScope
forall a. Ptr a
FP.nullPtr
        then BuilderScope -> Maybe BuilderScope
forall a. a -> Maybe a
P.Just (BuilderScope -> Maybe BuilderScope)
-> IO BuilderScope -> IO (Maybe BuilderScope)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr BuilderScope -> BuilderScope)
-> Ptr BuilderScope -> IO BuilderScope
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr BuilderScope -> BuilderScope
BuilderScope Ptr BuilderScope
ptr
        else Maybe BuilderScope -> IO (Maybe BuilderScope)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe BuilderScope
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList BuilderScope
type instance O.AttributeList BuilderScope = BuilderScopeAttributeList
type BuilderScopeAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

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

instance (info ~ ResolveBuilderScopeMethod t BuilderScope, O.OverloadedMethod info BuilderScope p) => OL.IsLabel t (BuilderScope -> 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 ~ ResolveBuilderScopeMethod t BuilderScope, O.OverloadedMethod info BuilderScope p, R.HasField t BuilderScope p) => R.HasField t BuilderScope p where
    getField = O.overloadedMethod @info

#endif

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

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList BuilderScope = BuilderScopeSignalList
type BuilderScopeSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif