{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Interfaces.Buildable
(
Buildable(..) ,
noBuildable ,
IsBuildable ,
toBuildable ,
#if defined(ENABLE_OVERLOADING)
ResolveBuildableMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
BuildableAddChildMethodInfo ,
#endif
buildableAddChild ,
#if defined(ENABLE_OVERLOADING)
BuildableConstructChildMethodInfo ,
#endif
buildableConstructChild ,
#if defined(ENABLE_OVERLOADING)
BuildableCustomFinishedMethodInfo ,
#endif
buildableCustomFinished ,
#if defined(ENABLE_OVERLOADING)
BuildableCustomTagEndMethodInfo ,
#endif
buildableCustomTagEnd ,
#if defined(ENABLE_OVERLOADING)
BuildableCustomTagStartMethodInfo ,
#endif
buildableCustomTagStart ,
#if defined(ENABLE_OVERLOADING)
BuildableGetInternalChildMethodInfo ,
#endif
buildableGetInternalChild ,
#if defined(ENABLE_OVERLOADING)
BuildableGetNameMethodInfo ,
#endif
buildableGetName ,
#if defined(ENABLE_OVERLOADING)
BuildableParserFinishedMethodInfo ,
#endif
buildableParserFinished ,
#if defined(ENABLE_OVERLOADING)
BuildableSetBuildablePropertyMethodInfo ,
#endif
buildableSetBuildableProperty ,
#if defined(ENABLE_OVERLOADING)
BuildableSetNameMethodInfo ,
#endif
buildableSetName ,
) 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.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 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.GLib.Structs.MarkupParser as GLib.MarkupParser
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Objects.Builder as Gtk.Builder
newtype Buildable = Buildable (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)
noBuildable :: Maybe Buildable
noBuildable :: Maybe Buildable
noBuildable = Maybe Buildable
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Buildable = BuildableSignalList
type BuildableSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_buildable_get_type"
c_gtk_buildable_get_type :: IO GType
instance GObject Buildable where
gobjectType :: IO GType
gobjectType = IO GType
c_gtk_buildable_get_type
instance B.GValue.IsGValue Buildable where
toGValue :: Buildable -> IO GValue
toGValue o :: Buildable
o = do
GType
gtype <- IO GType
c_gtk_buildable_get_type
Buildable -> (Ptr Buildable -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Buildable
o (GType
-> (GValue -> Ptr Buildable -> IO ()) -> Ptr Buildable -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Buildable -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO Buildable
fromGValue gv :: GValue
gv = do
Ptr Buildable
ptr <- GValue -> IO (Ptr Buildable)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Buildable)
(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
class (GObject o, O.IsDescendantOf Buildable o) => IsBuildable o
instance (GObject o, O.IsDescendantOf Buildable o) => IsBuildable o
instance O.HasParentTypes Buildable
type instance O.ParentTypes Buildable = '[GObject.Object.Object]
toBuildable :: (MonadIO m, IsBuildable o) => o -> m Buildable
toBuildable :: o -> m Buildable
toBuildable = IO Buildable -> m Buildable
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Buildable -> Buildable
Buildable
#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 "addChild" o = BuildableAddChildMethodInfo
ResolveBuildableMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveBuildableMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveBuildableMethod "constructChild" o = BuildableConstructChildMethodInfo
ResolveBuildableMethod "customFinished" o = BuildableCustomFinishedMethodInfo
ResolveBuildableMethod "customTagEnd" o = BuildableCustomTagEndMethodInfo
ResolveBuildableMethod "customTagStart" o = BuildableCustomTagStartMethodInfo
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 "parserFinished" o = BuildableParserFinishedMethodInfo
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 "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveBuildableMethod "getInternalChild" o = BuildableGetInternalChildMethodInfo
ResolveBuildableMethod "getName" o = BuildableGetNameMethodInfo
ResolveBuildableMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveBuildableMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveBuildableMethod "setBuildableProperty" o = BuildableSetBuildablePropertyMethodInfo
ResolveBuildableMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveBuildableMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveBuildableMethod "setName" o = BuildableSetNameMethodInfo
ResolveBuildableMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveBuildableMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveBuildableMethod t Buildable, O.MethodInfo 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
#endif
foreign import ccall "gtk_buildable_add_child" gtk_buildable_add_child ::
Ptr Buildable ->
Ptr Gtk.Builder.Builder ->
Ptr GObject.Object.Object ->
CString ->
IO ()
buildableAddChild ::
(B.CallStack.HasCallStack, MonadIO m, IsBuildable a, Gtk.Builder.IsBuilder b, GObject.Object.IsObject c) =>
a
-> b
-> c
-> Maybe (T.Text)
-> m ()
buildableAddChild :: a -> b -> c -> Maybe Text -> m ()
buildableAddChild buildable :: a
buildable builder :: b
builder child :: c
child type_ :: Maybe Text
type_ = 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 Buildable
buildable' <- a -> IO (Ptr Buildable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
buildable
Ptr Builder
builder' <- b -> IO (Ptr Builder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
builder
Ptr Object
child' <- c -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
child
Ptr CChar
maybeType_ <- case Maybe Text
type_ of
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just jType_ :: Text
jType_ -> do
Ptr CChar
jType_' <- Text -> IO (Ptr CChar)
textToCString Text
jType_
Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jType_'
Ptr Buildable -> Ptr Builder -> Ptr Object -> Ptr CChar -> IO ()
gtk_buildable_add_child Ptr Buildable
buildable' Ptr Builder
builder' Ptr Object
child' Ptr CChar
maybeType_
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
buildable
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
builder
c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr c
child
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeType_
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data BuildableAddChildMethodInfo
instance (signature ~ (b -> c -> Maybe (T.Text) -> m ()), MonadIO m, IsBuildable a, Gtk.Builder.IsBuilder b, GObject.Object.IsObject c) => O.MethodInfo BuildableAddChildMethodInfo a signature where
overloadedMethod = buildableAddChild
#endif
foreign import ccall "gtk_buildable_construct_child" gtk_buildable_construct_child ::
Ptr Buildable ->
Ptr Gtk.Builder.Builder ->
CString ->
IO (Ptr GObject.Object.Object)
buildableConstructChild ::
(B.CallStack.HasCallStack, MonadIO m, IsBuildable a, Gtk.Builder.IsBuilder b) =>
a
-> b
-> T.Text
-> m GObject.Object.Object
buildableConstructChild :: a -> b -> Text -> m Object
buildableConstructChild buildable :: a
buildable builder :: b
builder name :: Text
name = IO Object -> m Object
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Object -> m Object) -> IO Object -> m Object
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
Ptr Builder
builder' <- b -> IO (Ptr Builder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
builder
Ptr CChar
name' <- Text -> IO (Ptr CChar)
textToCString Text
name
Ptr Object
result <- Ptr Buildable -> Ptr Builder -> Ptr CChar -> IO (Ptr Object)
gtk_buildable_construct_child Ptr Buildable
buildable' Ptr Builder
builder' Ptr CChar
name'
Text -> Ptr Object -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "buildableConstructChild" Ptr Object
result
Object
result' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
buildable
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
builder
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
name'
Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result'
#if defined(ENABLE_OVERLOADING)
data BuildableConstructChildMethodInfo
instance (signature ~ (b -> T.Text -> m GObject.Object.Object), MonadIO m, IsBuildable a, Gtk.Builder.IsBuilder b) => O.MethodInfo BuildableConstructChildMethodInfo a signature where
overloadedMethod = buildableConstructChild
#endif
foreign import ccall "gtk_buildable_custom_finished" gtk_buildable_custom_finished ::
Ptr Buildable ->
Ptr Gtk.Builder.Builder ->
Ptr GObject.Object.Object ->
CString ->
Ptr () ->
IO ()
buildableCustomFinished ::
(B.CallStack.HasCallStack, MonadIO m, IsBuildable a, Gtk.Builder.IsBuilder b, GObject.Object.IsObject c) =>
a
-> b
-> Maybe (c)
-> T.Text
-> Ptr ()
-> m ()
buildableCustomFinished :: a -> b -> Maybe c -> Text -> Ptr () -> m ()
buildableCustomFinished buildable :: a
buildable builder :: b
builder child :: Maybe c
child tagname :: Text
tagname data_ :: Ptr ()
data_ = 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 Buildable
buildable' <- a -> IO (Ptr Buildable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
buildable
Ptr Builder
builder' <- b -> IO (Ptr Builder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
builder
Ptr Object
maybeChild <- case Maybe c
child of
Nothing -> Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
forall a. Ptr a
nullPtr
Just jChild :: c
jChild -> do
Ptr Object
jChild' <- c -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jChild
Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
jChild'
Ptr CChar
tagname' <- Text -> IO (Ptr CChar)
textToCString Text
tagname
Ptr Buildable
-> Ptr Builder -> Ptr Object -> Ptr CChar -> Ptr () -> IO ()
gtk_buildable_custom_finished Ptr Buildable
buildable' Ptr Builder
builder' Ptr Object
maybeChild Ptr CChar
tagname' Ptr ()
data_
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
buildable
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
builder
Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
child c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
tagname'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data BuildableCustomFinishedMethodInfo
instance (signature ~ (b -> Maybe (c) -> T.Text -> Ptr () -> m ()), MonadIO m, IsBuildable a, Gtk.Builder.IsBuilder b, GObject.Object.IsObject c) => O.MethodInfo BuildableCustomFinishedMethodInfo a signature where
overloadedMethod = buildableCustomFinished
#endif
foreign import ccall "gtk_buildable_custom_tag_end" gtk_buildable_custom_tag_end ::
Ptr Buildable ->
Ptr Gtk.Builder.Builder ->
Ptr GObject.Object.Object ->
CString ->
Ptr () ->
IO ()
buildableCustomTagEnd ::
(B.CallStack.HasCallStack, MonadIO m, IsBuildable a, Gtk.Builder.IsBuilder b, GObject.Object.IsObject c) =>
a
-> b
-> Maybe (c)
-> T.Text
-> Ptr ()
-> m ()
buildableCustomTagEnd :: a -> b -> Maybe c -> Text -> Ptr () -> m ()
buildableCustomTagEnd buildable :: a
buildable builder :: b
builder child :: Maybe c
child tagname :: Text
tagname data_ :: Ptr ()
data_ = 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 Buildable
buildable' <- a -> IO (Ptr Buildable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
buildable
Ptr Builder
builder' <- b -> IO (Ptr Builder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
builder
Ptr Object
maybeChild <- case Maybe c
child of
Nothing -> Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
forall a. Ptr a
nullPtr
Just jChild :: c
jChild -> do
Ptr Object
jChild' <- c -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jChild
Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
jChild'
Ptr CChar
tagname' <- Text -> IO (Ptr CChar)
textToCString Text
tagname
Ptr Buildable
-> Ptr Builder -> Ptr Object -> Ptr CChar -> Ptr () -> IO ()
gtk_buildable_custom_tag_end Ptr Buildable
buildable' Ptr Builder
builder' Ptr Object
maybeChild Ptr CChar
tagname' Ptr ()
data_
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
buildable
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
builder
Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
child c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
tagname'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data BuildableCustomTagEndMethodInfo
instance (signature ~ (b -> Maybe (c) -> T.Text -> Ptr () -> m ()), MonadIO m, IsBuildable a, Gtk.Builder.IsBuilder b, GObject.Object.IsObject c) => O.MethodInfo BuildableCustomTagEndMethodInfo a signature where
overloadedMethod = buildableCustomTagEnd
#endif
foreign import ccall "gtk_buildable_custom_tag_start" gtk_buildable_custom_tag_start ::
Ptr Buildable ->
Ptr Gtk.Builder.Builder ->
Ptr GObject.Object.Object ->
CString ->
Ptr GLib.MarkupParser.MarkupParser ->
Ptr (Ptr ()) ->
IO CInt
buildableCustomTagStart ::
(B.CallStack.HasCallStack, MonadIO m, IsBuildable a, Gtk.Builder.IsBuilder b, GObject.Object.IsObject c) =>
a
-> b
-> Maybe (c)
-> T.Text
-> m ((Bool, GLib.MarkupParser.MarkupParser, Ptr ()))
buildableCustomTagStart :: a -> b -> Maybe c -> Text -> m (Bool, MarkupParser, Ptr ())
buildableCustomTagStart buildable :: a
buildable builder :: b
builder child :: Maybe c
child tagname :: Text
tagname = IO (Bool, MarkupParser, Ptr ()) -> m (Bool, MarkupParser, Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, MarkupParser, Ptr ()) -> m (Bool, MarkupParser, Ptr ()))
-> IO (Bool, MarkupParser, Ptr ())
-> m (Bool, MarkupParser, Ptr ())
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
Ptr Builder
builder' <- b -> IO (Ptr Builder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
builder
Ptr Object
maybeChild <- case Maybe c
child of
Nothing -> Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
forall a. Ptr a
nullPtr
Just jChild :: c
jChild -> do
Ptr Object
jChild' <- c -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jChild
Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
jChild'
Ptr CChar
tagname' <- Text -> IO (Ptr CChar)
textToCString Text
tagname
Ptr MarkupParser
parser <- Int -> IO (Ptr MarkupParser)
forall a. Int -> IO (Ptr a)
callocBytes 40 :: IO (Ptr GLib.MarkupParser.MarkupParser)
Ptr (Ptr ())
data_ <- IO (Ptr (Ptr ()))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr ()))
CInt
result <- Ptr Buildable
-> Ptr Builder
-> Ptr Object
-> Ptr CChar
-> Ptr MarkupParser
-> Ptr (Ptr ())
-> IO CInt
gtk_buildable_custom_tag_start Ptr Buildable
buildable' Ptr Builder
builder' Ptr Object
maybeChild Ptr CChar
tagname' Ptr MarkupParser
parser Ptr (Ptr ())
data_
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
MarkupParser
parser' <- ((ManagedPtr MarkupParser -> MarkupParser)
-> Ptr MarkupParser -> IO MarkupParser
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr MarkupParser -> MarkupParser
GLib.MarkupParser.MarkupParser) Ptr MarkupParser
parser
Ptr ()
data_' <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr ())
data_
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
buildable
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
builder
Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
child c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
tagname'
Ptr (Ptr ()) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr ())
data_
(Bool, MarkupParser, Ptr ()) -> IO (Bool, MarkupParser, Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', MarkupParser
parser', Ptr ()
data_')
#if defined(ENABLE_OVERLOADING)
data BuildableCustomTagStartMethodInfo
instance (signature ~ (b -> Maybe (c) -> T.Text -> m ((Bool, GLib.MarkupParser.MarkupParser, Ptr ()))), MonadIO m, IsBuildable a, Gtk.Builder.IsBuilder b, GObject.Object.IsObject c) => O.MethodInfo BuildableCustomTagStartMethodInfo a signature where
overloadedMethod = buildableCustomTagStart
#endif
foreign import ccall "gtk_buildable_get_internal_child" gtk_buildable_get_internal_child ::
Ptr Buildable ->
Ptr Gtk.Builder.Builder ->
CString ->
IO (Ptr GObject.Object.Object)
buildableGetInternalChild ::
(B.CallStack.HasCallStack, MonadIO m, IsBuildable a, Gtk.Builder.IsBuilder b) =>
a
-> b
-> T.Text
-> m GObject.Object.Object
buildableGetInternalChild :: a -> b -> Text -> m Object
buildableGetInternalChild buildable :: a
buildable builder :: b
builder childname :: Text
childname = IO Object -> m Object
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Object -> m Object) -> IO Object -> m Object
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
Ptr Builder
builder' <- b -> IO (Ptr Builder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
builder
Ptr CChar
childname' <- Text -> IO (Ptr CChar)
textToCString Text
childname
Ptr Object
result <- Ptr Buildable -> Ptr Builder -> Ptr CChar -> IO (Ptr Object)
gtk_buildable_get_internal_child Ptr Buildable
buildable' Ptr Builder
builder' Ptr CChar
childname'
Text -> Ptr Object -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "buildableGetInternalChild" Ptr Object
result
Object
result' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
buildable
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
builder
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
childname'
Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result'
#if defined(ENABLE_OVERLOADING)
data BuildableGetInternalChildMethodInfo
instance (signature ~ (b -> T.Text -> m GObject.Object.Object), MonadIO m, IsBuildable a, Gtk.Builder.IsBuilder b) => O.MethodInfo BuildableGetInternalChildMethodInfo a signature where
overloadedMethod = buildableGetInternalChild
#endif
foreign import ccall "gtk_buildable_get_name" gtk_buildable_get_name ::
Ptr Buildable ->
IO CString
buildableGetName ::
(B.CallStack.HasCallStack, MonadIO m, IsBuildable a) =>
a
-> m T.Text
buildableGetName :: a -> m Text
buildableGetName buildable :: 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
Ptr CChar
result <- Ptr Buildable -> IO (Ptr CChar)
gtk_buildable_get_name Ptr Buildable
buildable'
Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "buildableGetName" Ptr CChar
result
Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
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 BuildableGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsBuildable a) => O.MethodInfo BuildableGetNameMethodInfo a signature where
overloadedMethod = buildableGetName
#endif
foreign import ccall "gtk_buildable_parser_finished" gtk_buildable_parser_finished ::
Ptr Buildable ->
Ptr Gtk.Builder.Builder ->
IO ()
buildableParserFinished ::
(B.CallStack.HasCallStack, MonadIO m, IsBuildable a, Gtk.Builder.IsBuilder b) =>
a
-> b
-> m ()
buildableParserFinished :: a -> b -> m ()
buildableParserFinished buildable :: a
buildable builder :: b
builder = 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 Buildable
buildable' <- a -> IO (Ptr Buildable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
buildable
Ptr Builder
builder' <- b -> IO (Ptr Builder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
builder
Ptr Buildable -> Ptr Builder -> IO ()
gtk_buildable_parser_finished Ptr Buildable
buildable' Ptr Builder
builder'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
buildable
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
builder
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data BuildableParserFinishedMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsBuildable a, Gtk.Builder.IsBuilder b) => O.MethodInfo BuildableParserFinishedMethodInfo a signature where
overloadedMethod = buildableParserFinished
#endif
foreign import ccall "gtk_buildable_set_buildable_property" gtk_buildable_set_buildable_property ::
Ptr Buildable ->
Ptr Gtk.Builder.Builder ->
CString ->
Ptr GValue ->
IO ()
buildableSetBuildableProperty ::
(B.CallStack.HasCallStack, MonadIO m, IsBuildable a, Gtk.Builder.IsBuilder b) =>
a
-> b
-> T.Text
-> GValue
-> m ()
buildableSetBuildableProperty :: a -> b -> Text -> GValue -> m ()
buildableSetBuildableProperty buildable :: a
buildable builder :: b
builder name :: Text
name value :: GValue
value = 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 Buildable
buildable' <- a -> IO (Ptr Buildable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
buildable
Ptr Builder
builder' <- b -> IO (Ptr Builder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
builder
Ptr CChar
name' <- Text -> IO (Ptr CChar)
textToCString Text
name
Ptr GValue
value' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
value
Ptr Buildable -> Ptr Builder -> Ptr CChar -> Ptr GValue -> IO ()
gtk_buildable_set_buildable_property Ptr Buildable
buildable' Ptr Builder
builder' Ptr CChar
name' Ptr GValue
value'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
buildable
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
builder
GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
value
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
name'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data BuildableSetBuildablePropertyMethodInfo
instance (signature ~ (b -> T.Text -> GValue -> m ()), MonadIO m, IsBuildable a, Gtk.Builder.IsBuilder b) => O.MethodInfo BuildableSetBuildablePropertyMethodInfo a signature where
overloadedMethod = buildableSetBuildableProperty
#endif
foreign import ccall "gtk_buildable_set_name" gtk_buildable_set_name ::
Ptr Buildable ->
CString ->
IO ()
buildableSetName ::
(B.CallStack.HasCallStack, MonadIO m, IsBuildable a) =>
a
-> T.Text
-> m ()
buildableSetName :: a -> Text -> m ()
buildableSetName buildable :: a
buildable name :: Text
name = 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 Buildable
buildable' <- a -> IO (Ptr Buildable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
buildable
Ptr CChar
name' <- Text -> IO (Ptr CChar)
textToCString Text
name
Ptr Buildable -> Ptr CChar -> IO ()
gtk_buildable_set_name Ptr Buildable
buildable' Ptr CChar
name'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
buildable
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
name'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data BuildableSetNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsBuildable a) => O.MethodInfo BuildableSetNameMethodInfo a signature where
overloadedMethod = buildableSetName
#endif