{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Interfaces.Buildable
(
Buildable(..) ,
IsBuildable ,
toBuildable ,
#if defined(ENABLE_OVERLOADING)
ResolveBuildableMethod ,
#endif
#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.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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GObject.Objects.Object as GObject.Object
#else
import qualified GI.GObject.Objects.Object as GObject.Object
#endif
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
$c== :: Buildable -> Buildable -> Bool
== :: Buildable -> Buildable -> Bool
$c/= :: Buildable -> Buildable -> Bool
/= :: 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
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]
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 a. IO a -> m a
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
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 a. a -> IO a
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, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveBuildableMethod (t :: Symbol) (o :: DK.Type) :: DK.Type 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
foreign import ccall "gtk_buildable_get_buildable_id" gtk_buildable_get_buildable_id ::
Ptr Buildable ->
IO CString
buildableGetBuildableId ::
(B.CallStack.HasCallStack, MonadIO m, IsBuildable a) =>
a
-> m (Maybe T.Text)
buildableGetBuildableId :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBuildable a) =>
a -> m (Maybe Text)
buildableGetBuildableId a
buildable = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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 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'
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
$ \CString
result' -> do
Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
buildable
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data BuildableGetBuildableIdMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsBuildable a) => O.OverloadedMethod BuildableGetBuildableIdMethodInfo a signature where
overloadedMethod = buildableGetBuildableId
instance O.OverloadedMethodInfo BuildableGetBuildableIdMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.Buildable.buildableGetBuildableId",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.10/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, DK.Type)])
#endif