module GI.Gtk.Objects.TextChildAnchor
(
TextChildAnchor(..) ,
TextChildAnchorK ,
toTextChildAnchor ,
noTextChildAnchor ,
textChildAnchorGetDeleted ,
textChildAnchorGetWidgets ,
textChildAnchorNew ,
) where
import Prelude ()
import Data.GI.Base.ShortPrelude
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import GI.Gtk.Types
import GI.Gtk.Callbacks
import qualified GI.GObject as GObject
newtype TextChildAnchor = TextChildAnchor (ForeignPtr TextChildAnchor)
foreign import ccall "gtk_text_child_anchor_get_type"
c_gtk_text_child_anchor_get_type :: IO GType
type instance ParentTypes TextChildAnchor = TextChildAnchorParentTypes
type TextChildAnchorParentTypes = '[GObject.Object]
instance GObject TextChildAnchor where
gobjectIsInitiallyUnowned _ = False
gobjectType _ = c_gtk_text_child_anchor_get_type
class GObject o => TextChildAnchorK o
instance (GObject o, IsDescendantOf TextChildAnchor o) => TextChildAnchorK o
toTextChildAnchor :: TextChildAnchorK o => o -> IO TextChildAnchor
toTextChildAnchor = unsafeCastTo TextChildAnchor
noTextChildAnchor :: Maybe TextChildAnchor
noTextChildAnchor = Nothing
type instance AttributeList TextChildAnchor = TextChildAnchorAttributeList
type TextChildAnchorAttributeList = ('[ ] :: [(Symbol, *)])
type instance SignalList TextChildAnchor = TextChildAnchorSignalList
type TextChildAnchorSignalList = ('[ '("notify", GObject.ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])
foreign import ccall "gtk_text_child_anchor_new" gtk_text_child_anchor_new ::
IO (Ptr TextChildAnchor)
textChildAnchorNew ::
(MonadIO m) =>
m TextChildAnchor
textChildAnchorNew = liftIO $ do
result <- gtk_text_child_anchor_new
checkUnexpectedReturnNULL "gtk_text_child_anchor_new" result
result' <- (wrapObject TextChildAnchor) result
return result'
foreign import ccall "gtk_text_child_anchor_get_deleted" gtk_text_child_anchor_get_deleted ::
Ptr TextChildAnchor ->
IO CInt
textChildAnchorGetDeleted ::
(MonadIO m, TextChildAnchorK a) =>
a ->
m Bool
textChildAnchorGetDeleted _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- gtk_text_child_anchor_get_deleted _obj'
let result' = (/= 0) result
touchManagedPtr _obj
return result'
foreign import ccall "gtk_text_child_anchor_get_widgets" gtk_text_child_anchor_get_widgets ::
Ptr TextChildAnchor ->
IO (Ptr (GList (Ptr Widget)))
textChildAnchorGetWidgets ::
(MonadIO m, TextChildAnchorK a) =>
a ->
m [Widget]
textChildAnchorGetWidgets _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- gtk_text_child_anchor_get_widgets _obj'
checkUnexpectedReturnNULL "gtk_text_child_anchor_get_widgets" result
result' <- unpackGList result
result'' <- mapM (newObject Widget) result'
g_list_free result
touchManagedPtr _obj
return result''