{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.TextChildAnchor
(
TextChildAnchor(..) ,
IsTextChildAnchor ,
toTextChildAnchor ,
noTextChildAnchor ,
#if defined(ENABLE_OVERLOADING)
ResolveTextChildAnchorMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
TextChildAnchorGetDeletedMethodInfo ,
#endif
textChildAnchorGetDeleted ,
#if defined(ENABLE_OVERLOADING)
TextChildAnchorGetWidgetsMethodInfo ,
#endif
textChildAnchorGetWidgets ,
textChildAnchorNew ,
) 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.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
newtype TextChildAnchor = TextChildAnchor (ManagedPtr TextChildAnchor)
deriving (TextChildAnchor -> TextChildAnchor -> Bool
(TextChildAnchor -> TextChildAnchor -> Bool)
-> (TextChildAnchor -> TextChildAnchor -> Bool)
-> Eq TextChildAnchor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextChildAnchor -> TextChildAnchor -> Bool
$c/= :: TextChildAnchor -> TextChildAnchor -> Bool
== :: TextChildAnchor -> TextChildAnchor -> Bool
$c== :: TextChildAnchor -> TextChildAnchor -> Bool
Eq)
foreign import ccall "gtk_text_child_anchor_get_type"
c_gtk_text_child_anchor_get_type :: IO GType
instance GObject TextChildAnchor where
gobjectType :: IO GType
gobjectType = IO GType
c_gtk_text_child_anchor_get_type
instance B.GValue.IsGValue TextChildAnchor where
toGValue :: TextChildAnchor -> IO GValue
toGValue o :: TextChildAnchor
o = do
GType
gtype <- IO GType
c_gtk_text_child_anchor_get_type
TextChildAnchor -> (Ptr TextChildAnchor -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TextChildAnchor
o (GType
-> (GValue -> Ptr TextChildAnchor -> IO ())
-> Ptr TextChildAnchor
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr TextChildAnchor -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO TextChildAnchor
fromGValue gv :: GValue
gv = do
Ptr TextChildAnchor
ptr <- GValue -> IO (Ptr TextChildAnchor)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr TextChildAnchor)
(ManagedPtr TextChildAnchor -> TextChildAnchor)
-> Ptr TextChildAnchor -> IO TextChildAnchor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr TextChildAnchor -> TextChildAnchor
TextChildAnchor Ptr TextChildAnchor
ptr
class (GObject o, O.IsDescendantOf TextChildAnchor o) => IsTextChildAnchor o
instance (GObject o, O.IsDescendantOf TextChildAnchor o) => IsTextChildAnchor o
instance O.HasParentTypes TextChildAnchor
type instance O.ParentTypes TextChildAnchor = '[GObject.Object.Object]
toTextChildAnchor :: (MonadIO m, IsTextChildAnchor o) => o -> m TextChildAnchor
toTextChildAnchor :: o -> m TextChildAnchor
toTextChildAnchor = IO TextChildAnchor -> m TextChildAnchor
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextChildAnchor -> m TextChildAnchor)
-> (o -> IO TextChildAnchor) -> o -> m TextChildAnchor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr TextChildAnchor -> TextChildAnchor)
-> o -> IO TextChildAnchor
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr TextChildAnchor -> TextChildAnchor
TextChildAnchor
noTextChildAnchor :: Maybe TextChildAnchor
noTextChildAnchor :: Maybe TextChildAnchor
noTextChildAnchor = Maybe TextChildAnchor
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveTextChildAnchorMethod (t :: Symbol) (o :: *) :: * where
ResolveTextChildAnchorMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveTextChildAnchorMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveTextChildAnchorMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveTextChildAnchorMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveTextChildAnchorMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveTextChildAnchorMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveTextChildAnchorMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveTextChildAnchorMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveTextChildAnchorMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveTextChildAnchorMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveTextChildAnchorMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveTextChildAnchorMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveTextChildAnchorMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveTextChildAnchorMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveTextChildAnchorMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveTextChildAnchorMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveTextChildAnchorMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveTextChildAnchorMethod "getDeleted" o = TextChildAnchorGetDeletedMethodInfo
ResolveTextChildAnchorMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveTextChildAnchorMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveTextChildAnchorMethod "getWidgets" o = TextChildAnchorGetWidgetsMethodInfo
ResolveTextChildAnchorMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveTextChildAnchorMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveTextChildAnchorMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveTextChildAnchorMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTextChildAnchorMethod t TextChildAnchor, O.MethodInfo info TextChildAnchor p) => OL.IsLabel t (TextChildAnchor -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TextChildAnchor
type instance O.AttributeList TextChildAnchor = TextChildAnchorAttributeList
type TextChildAnchorAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TextChildAnchor = TextChildAnchorSignalList
type TextChildAnchorSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_text_child_anchor_new" gtk_text_child_anchor_new ::
IO (Ptr TextChildAnchor)
textChildAnchorNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m TextChildAnchor
textChildAnchorNew :: m TextChildAnchor
textChildAnchorNew = IO TextChildAnchor -> m TextChildAnchor
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextChildAnchor -> m TextChildAnchor)
-> IO TextChildAnchor -> m TextChildAnchor
forall a b. (a -> b) -> a -> b
$ do
Ptr TextChildAnchor
result <- IO (Ptr TextChildAnchor)
gtk_text_child_anchor_new
Text -> Ptr TextChildAnchor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "textChildAnchorNew" Ptr TextChildAnchor
result
TextChildAnchor
result' <- ((ManagedPtr TextChildAnchor -> TextChildAnchor)
-> Ptr TextChildAnchor -> IO TextChildAnchor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TextChildAnchor -> TextChildAnchor
TextChildAnchor) Ptr TextChildAnchor
result
TextChildAnchor -> IO TextChildAnchor
forall (m :: * -> *) a. Monad m => a -> m a
return TextChildAnchor
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_text_child_anchor_get_deleted" gtk_text_child_anchor_get_deleted ::
Ptr TextChildAnchor ->
IO CInt
textChildAnchorGetDeleted ::
(B.CallStack.HasCallStack, MonadIO m, IsTextChildAnchor a) =>
a
-> m Bool
textChildAnchorGetDeleted :: a -> m Bool
textChildAnchorGetDeleted anchor :: a
anchor = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr TextChildAnchor
anchor' <- a -> IO (Ptr TextChildAnchor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
anchor
CInt
result <- Ptr TextChildAnchor -> IO CInt
gtk_text_child_anchor_get_deleted Ptr TextChildAnchor
anchor'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
anchor
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TextChildAnchorGetDeletedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTextChildAnchor a) => O.MethodInfo TextChildAnchorGetDeletedMethodInfo a signature where
overloadedMethod = textChildAnchorGetDeleted
#endif
foreign import ccall "gtk_text_child_anchor_get_widgets" gtk_text_child_anchor_get_widgets ::
Ptr TextChildAnchor ->
IO (Ptr (GList (Ptr Gtk.Widget.Widget)))
textChildAnchorGetWidgets ::
(B.CallStack.HasCallStack, MonadIO m, IsTextChildAnchor a) =>
a
-> m [Gtk.Widget.Widget]
textChildAnchorGetWidgets :: a -> m [Widget]
textChildAnchorGetWidgets anchor :: a
anchor = IO [Widget] -> m [Widget]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Widget] -> m [Widget]) -> IO [Widget] -> m [Widget]
forall a b. (a -> b) -> a -> b
$ do
Ptr TextChildAnchor
anchor' <- a -> IO (Ptr TextChildAnchor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
anchor
Ptr (GList (Ptr Widget))
result <- Ptr TextChildAnchor -> IO (Ptr (GList (Ptr Widget)))
gtk_text_child_anchor_get_widgets Ptr TextChildAnchor
anchor'
[Ptr Widget]
result' <- Ptr (GList (Ptr Widget)) -> IO [Ptr Widget]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr Widget))
result
[Widget]
result'' <- (Ptr Widget -> IO Widget) -> [Ptr Widget] -> IO [Widget]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) [Ptr Widget]
result'
Ptr (GList (Ptr Widget)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr Widget))
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
anchor
[Widget] -> IO [Widget]
forall (m :: * -> *) a. Monad m => a -> m a
return [Widget]
result''
#if defined(ENABLE_OVERLOADING)
data TextChildAnchorGetWidgetsMethodInfo
instance (signature ~ (m [Gtk.Widget.Widget]), MonadIO m, IsTextChildAnchor a) => O.MethodInfo TextChildAnchorGetWidgetsMethodInfo a signature where
overloadedMethod = textChildAnchorGetWidgets
#endif