{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- GtkBuildable allows objects to extend and customize their deserialization
-- from [GtkBuilder UI descriptions][BUILDER-UI].
-- The interface includes methods for setting names and properties of objects,
-- parsing custom tags and constructing child objects.
-- 
-- The GtkBuildable interface is implemented by all widgets and
-- many of the non-widget objects that are provided by GTK. The
-- main user of this interface is t'GI.Gtk.Objects.Builder.Builder'. There should be
-- very little need for applications to call any of these functions directly.
-- 
-- An object only needs to implement this interface if it needs to extend the
-- t'GI.Gtk.Objects.Builder.Builder' format or run any extra routines at deserialization time.

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

module GI.Gtk.Interfaces.Buildable
    ( 

-- * Exported types
    Buildable(..)                           ,
    IsBuildable                             ,
    toBuildable                             ,


 -- * 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
-- [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [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)
    ResolveBuildableMethod                  ,
#endif

-- ** getBuildableId #method:getBuildableId#

#if defined(ENABLE_OVERLOADING)
    BuildableGetBuildableIdMethodInfo       ,
#endif
    buildableGetBuildableId                 ,




    ) 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.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

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

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

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

foreign import ccall "gtk_buildable_get_type"
    c_gtk_buildable_get_type :: IO B.Types.GType

instance B.Types.TypedObject Buildable where
    glibType :: IO GType
glibType = IO GType
c_gtk_buildable_get_type

instance B.Types.GObject Buildable

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

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

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

-- | Convert 'Buildable' 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 Buildable) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_buildable_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Buildable -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Buildable
P.Nothing = Ptr GValue -> Ptr Buildable -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Buildable
forall a. Ptr a
FP.nullPtr :: FP.Ptr Buildable)
    gvalueSet_ Ptr GValue
gv (P.Just Buildable
obj) = Buildable -> (Ptr Buildable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Buildable
obj (Ptr GValue -> Ptr Buildable -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Buildable)
gvalueGet_ Ptr GValue
gv = do
        Ptr Buildable
ptr <- Ptr GValue -> IO (Ptr Buildable)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Buildable)
        if Ptr Buildable
ptr Ptr Buildable -> Ptr Buildable -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Buildable
forall a. Ptr a
FP.nullPtr
        then Buildable -> Maybe Buildable
forall a. a -> Maybe a
P.Just (Buildable -> Maybe Buildable)
-> IO Buildable -> IO (Maybe Buildable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Buildable -> Buildable)
-> Ptr Buildable -> IO Buildable
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Buildable -> Buildable
Buildable Ptr Buildable
ptr
        else Maybe Buildable -> IO (Maybe Buildable)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Buildable
forall a. Maybe a
P.Nothing
        
    

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

#if defined(ENABLE_OVERLOADING)
#endif

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

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

#endif

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

#endif

-- method Buildable::get_buildable_id
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "buildable"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Buildable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkBuildable" , 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 "gtk_buildable_get_buildable_id" gtk_buildable_get_buildable_id :: 
    Ptr Buildable ->                        -- buildable : TInterface (Name {namespace = "Gtk", name = "Buildable"})
    IO CString

-- | Gets the ID of the /@buildable@/ object.
-- 
-- t'GI.Gtk.Objects.Builder.Builder' sets the name based on the
-- [GtkBuilder UI definition][BUILDER-UI]
-- used to construct the /@buildable@/.
buildableGetBuildableId ::
    (B.CallStack.HasCallStack, MonadIO m, IsBuildable a) =>
    a
    -- ^ /@buildable@/: a t'GI.Gtk.Interfaces.Buildable.Buildable'
    -> m T.Text
    -- ^ __Returns:__ the ID set with @/gtk_buildable_set_buildable_id()/@
buildableGetBuildableId :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBuildable a) =>
a -> m Text
buildableGetBuildableId a
buildable = 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 Buildable
buildable' <- a -> IO (Ptr Buildable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
buildable
    CString
result <- Ptr Buildable -> IO CString
gtk_buildable_get_buildable_id Ptr Buildable
buildable'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"buildableGetBuildableId" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
buildable
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data BuildableGetBuildableIdMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsBuildable a) => O.OverloadedMethod BuildableGetBuildableIdMethodInfo a signature where
    overloadedMethod = buildableGetBuildableId

instance O.OverloadedMethodInfo BuildableGetBuildableIdMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Interfaces.Buildable.buildableGetBuildableId",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Interfaces-Buildable.html#v:buildableGetBuildableId"
        }


#endif

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

#endif